Action

From HaskellWiki
Jump to navigation Jump to search

An action is a value that, if performed, may have an effect upon some context in order to produce its result. (Actions are sometimes referred to as computations in earlier texts.)

In Haskell, actions usually have an abstract monadic type. For example:

  • IO a, the type of I/O actions;
  • ST s a, the type of encapsulated-state actions.

The condition that an action's effects only occur if performed prevents their use in otherwise-ordinary Haskell definitions. For example the following won't work:

(\ a -> case newSTArray (bounds a) False of !va -> va)

because Haskell cannot evaluate newSTArray (bounds g) False by itself - a context is required, one provided by runST:

type Graph = Array Vertex [Vertex]
data Tree a = Node a [Tree a]

dfs :: Graph -> [Vertex] -> [Tree Vertex]
dfs g vs = runST (
              newSTArray (bounds g) False >>= \ marks ->
              search marks vs
           )
  where search :: STArray s Vertex Bool -> [Vertex]
                  -> ST s [Tree Vertex]
        search marks   []   = return []
        search marks (v:vs) = readSTArray marks v >>= \ visited ->
                              if visited then
                                 search marks vs
                              else
                                writeSTArray marks v True >>
                                search marks (g!v)    >>= \ ts ->
                                search marks vs       >>= \ us ->
                                return ((Node v ts): us)
from Figure 2 (page 17 of 51) of State in Haskell

Similarly, this too won't work:

trace msg x = case putStrLn msg of !_ -> x

as putStrLn msg also requires a context:

There is really only one [safe] way to "perform" an I/O action: bind it to Main.main in your program. When your program is run, the I/O will be performed. It isn't possible to perform I/O from an arbitrary function, unless that function is itself in the IO monad and called at some point, directly or indirectly, from Main.main.

GHC.IO - Hackage

Main.main is also an action, so it requires a context as well. But unlike ST s a, that is provided by the Haskell implementation itself.

So actions exist as a separate group between imperative procedures and ordinary Haskell values, having some properties of each:

  • like other Haskell values, they can be inertly passed from definition to definition,
  • but like imperative procedures, they can have effects (when used in the appropriate context).