Difference between revisions of "Monad/ST"

From HaskellWiki
Jump to navigation Jump to search
m (Auxiliary reference added)
 
(10 intermediate revisions by 8 users not shown)
Line 1: Line 1:
 
{{Standard class|ST|module=Control.Monad.ST|module-doc=Control-Monad-ST|package=base}}
 
{{Standard class|ST|module=Control.Monad.ST|module-doc=Control-Monad-ST|package=base}}
   
The ST monad provides support for ''strict'' state threads.
+
The monadic <code>ST</code> type provides support for ''strict'' state threads.
   
   
 
==A discussion on the Haskell irc ==
 
==A discussion on the Haskell irc ==
 
From #haskell (see 13:05:37 in the [http://tunes.org/~nef/logs/haskell/07.02.07 log] ):
 
From #haskell (see 13:05:37 in the [http://tunes.org/~nef/logs/haskell/07.02.07 log] ):
  +
<tt>
 
 
* TuringTest: ST lets you implement algorithms that are much more efficient with mutable memory used internally. But the whole "thread" of computation cannot exchange mutable state with the outside world, it can only exchange immutable state.
 
* TuringTest: ST lets you implement algorithms that are much more efficient with mutable memory used internally. But the whole "thread" of computation cannot exchange mutable state with the outside world, it can only exchange immutable state.
   
Line 14: Line 14:
   
 
* DapperDan2: it strikes me that ST is like a lexical scope, where all the variables/state disappear when the function returns.
 
* DapperDan2: it strikes me that ST is like a lexical scope, where all the variables/state disappear when the function returns.
  +
</tt>
 
[[Category:Standard classes]] [[Category:Monad]]
 
[[Category:Standard classes]] [[Category:Monad]]
 
   
 
==An explanation in Haskell-Cafe==
 
==An explanation in Haskell-Cafe==
   
The ST monad lets you use update-in-place, but is escapable (unlike IO).
+
The ST type lets you use update-in-place, but is escapable (unlike <code>IO</code>).
ST actions have the form:
+
<code>ST</code> actions have the form:
   
 
<haskell>
 
<haskell>
Line 26: Line 26:
 
</haskell>
 
</haskell>
   
Meaning that they return a value of type α, and execute in "thread" s.
+
Meaning that they return a value of type <code>α</code>, and execute in "thread" <code>s</code>. All reference types are tagged with the thread, so that actions can only affect references in their own "thread".
All reference types are tagged with the thread, so that actions can only
 
affect references in their own "thread".
 
   
Now, the type of the function used to escape ST is:
+
Now, the type of the function used to escape <code>ST</code> is:
   
 
<haskell>
 
<haskell>
Line 36: Line 34:
 
</haskell>
 
</haskell>
   
 
The action you pass must be universal in <code>s</code>, so inside your action you don't know what thread, thus you cannot access any other threads, thus <hask>runST</hask> is pure. This is very useful, since it allows you to implement externally pure things like in-place quicksort, and present them as pure functions <code>∀ e. Ord e ⇒ Array e → Array e</code>; without using any unsafe definitions.
The action you pass must be universal in s, so inside your action you
 
don't know what thread, thus you cannot access any other threads, thus
 
<hask>runST</hask> is pure. This is very useful, since it allows you to implement externally pure things like in-place quicksort, and present them as pure functions ∀ e. Ord e ⇒ Array e → Array e; without using any unsafe functions.
 
   
But that type of <hask>runST</hask> is illegal in Haskell-98, because it needs a universal quantifier *inside* the function-arrow! In the jargon, that
+
But that type of <hask>runST</hask> is illegal in Haskell-98, because it needs a universal quantifier ''inside'' the function-arrow! In the jargon, that type has rank 2; Haskell-98 types may have rank at most 1.
type has rank 2; haskell 98 types may have rank at most 1.
 
   
 
See http://www.haskell.org/pipermail/haskell-cafe/2007-July/028233.html
 
See http://www.haskell.org/pipermail/haskell-cafe/2007-July/028233.html
 
Could we *please* see an example.
 
 
Sure thing...
 
   
 
== A few simple examples ==
 
== A few simple examples ==
   
In this example, we define a version of the function sum, but do it in a way which more like how it would be done in imperative languages, where a variable is updated, rather than a new value is formed and passed to the next iteration of the function. While in place modifications of the STRef n are occurring, something that would usually be considered a side effect, it is all done in a safe way which is deterministic. The result is that we get the benefits of being able to modify memory in place, while still producing a pure function with the use of runST.
+
In this example, we define a version of the function <code>sum</code>, but do it in a way which more like how it would be done in imperative languages, where a variable is updated, rather than a new value is formed and passed to the next iteration of the function. While in-place modifications of the <code>STRef</code> <code>n</code> are occurring, something that would usually be considered a side effect, it is all done in a safe way which is deterministic. The result is that we get the benefits of being able to modify memory in-place, while still producing a pure function with the use of <code>runST</code>.
   
 
<haskell>
 
<haskell>
Line 72: Line 63:
 
</haskell>
 
</haskell>
   
An implementation of foldl using the ST monad (a lot like sum, and in fact sum can be defined in terms of foldlST):
+
An implementation of <code>foldl</code> using <code>ST</code> (a lot like <code>sum</code>, and in fact <code>sum</code> can be defined in terms of <code>foldlST</code>):
   
 
<haskell>
 
<haskell>
Line 104: Line 95:
 
y' <- readSTRef y
 
y' <- readSTRef y
 
writeSTRef x y'
 
writeSTRef x y'
writeSTRef y (x'+y')
+
writeSTRef y $! x'+y'
 
fibST' (n-1) x y
 
fibST' (n-1) x y
 
</haskell>
 
</haskell>
  +
[1] (Since we're using Integers, technically it's not constant space, as they grow in size when they get bigger, but we can ignore this.)
+
<sup>[1] Since we're using <code>Integers</code>, technically it's not constant space, as they grow in size when they get bigger, but we can ignore this</sup>.
  +
  +
== References ==
  +
* [https://citeseerx.ist.psu.edu/viewdoc/download?doi=10.1.1.50.3299&rep=rep1&type=pdf Lazy Functional State Threads], John Launchbury and Simon Peyton Jones (the authors of [https://citeseerx.ist.psu.edu/viewdoc/download?doi=10.1.1.52.3656&rep=rep1&type=pdf State in Haskell]).
  +
* [https://hackage.haskell.org/package/base/docs/Control-Monad-ST.html Control.Monad.ST] in the base libraries

Latest revision as of 05:38, 4 August 2021

ST class (base)
import Control.Monad.ST

The monadic ST type provides support for strict state threads.


A discussion on the Haskell irc

From #haskell (see 13:05:37 in the log ):

  • TuringTest: ST lets you implement algorithms that are much more efficient with mutable memory used internally. But the whole "thread" of computation cannot exchange mutable state with the outside world, it can only exchange immutable state.
  • TuringTest: chessguy: You pass in normal Haskell values and then use ST to allocate mutable memory, then you initialize and play with it, then you put it away and return a normal Haskell value.
  • sjanssen: a monad that has mutable references and arrays, but has a "run" function that is referentially transparent
  • DapperDan2: it strikes me that ST is like a lexical scope, where all the variables/state disappear when the function returns.

An explanation in Haskell-Cafe

The ST type lets you use update-in-place, but is escapable (unlike IO). ST actions have the form:

ST s α

Meaning that they return a value of type α, and execute in "thread" s. All reference types are tagged with the thread, so that actions can only affect references in their own "thread".

Now, the type of the function used to escape ST is:

runST :: forall α. (forall s. ST s α) -> α

The action you pass must be universal in s, so inside your action you don't know what thread, thus you cannot access any other threads, thus runST is pure. This is very useful, since it allows you to implement externally pure things like in-place quicksort, and present them as pure functions ∀ e. Ord e ⇒ Array e → Array e; without using any unsafe definitions.

But that type of runST is illegal in Haskell-98, because it needs a universal quantifier inside the function-arrow! In the jargon, that type has rank 2; Haskell-98 types may have rank at most 1.

See http://www.haskell.org/pipermail/haskell-cafe/2007-July/028233.html

A few simple examples

In this example, we define a version of the function sum, but do it in a way which more like how it would be done in imperative languages, where a variable is updated, rather than a new value is formed and passed to the next iteration of the function. While in-place modifications of the STRef n are occurring, something that would usually be considered a side effect, it is all done in a safe way which is deterministic. The result is that we get the benefits of being able to modify memory in-place, while still producing a pure function with the use of runST.

import Control.Monad.ST
import Data.STRef
import Control.Monad


sumST :: Num a => [a] -> a
sumST xs = runST $ do           -- runST takes out stateful code and makes it pure again.

    n <- newSTRef 0             -- Create an STRef (place in memory to store values)

    forM_ xs $ \x -> do         -- For each element of xs ..
        modifySTRef n (+x)      -- add it to what we have in n.

    readSTRef n                 -- read the value of n, and return it.

An implementation of foldl using ST (a lot like sum, and in fact sum can be defined in terms of foldlST):

foldlST :: (a -> b -> a) -> a -> [b] -> a
foldlST f acc xs = runST $ do
    acc' <- newSTRef acc            -- Create a variable for the accumulator

    forM_ xs $ \x -> do             -- For each x in xs...

        a <- readSTRef acc'         -- read the accumulator
        writeSTRef acc' (f a x)     -- apply f to the accumulator and x

    readSTRef acc'                  -- and finally read the result

An example of the Fibonacci function running in constant¹ space:

fibST :: Integer -> Integer
fibST n = 
    if n < 2
    then n
    else runST $ do
        x <- newSTRef 0
        y <- newSTRef 1
        fibST' n x y

    where fibST' 0 x _ = readSTRef x
          fibST' n x y = do
              x' <- readSTRef x
              y' <- readSTRef y
              writeSTRef x y'
              writeSTRef y $! x'+y'
              fibST' (n-1) x y

[1] Since we're using Integers, technically it's not constant space, as they grow in size when they get bigger, but we can ignore this.

References