3a_asm: ghc flags
[calu.git] / 3a_asm / Control / Monad / Reader / Class.hs
1 {-# LANGUAGE FlexibleInstances, UndecidableInstances, MultiParamTypeClasses, FunctionalDependencies, TypeSynonymInstances #-}
2 {- |
3 Module      :  Control.Monad.Reader.Class
4 Copyright   :  (c) Andy Gill 2001,
5                (c) Oregon Graduate Institute of Science and Technology 2001,
6                (c) Jeff Newbern 2003-2007,
7                (c) Andriy Palamarchuk 2007
8 License     :  BSD-style (see the file libraries/base/LICENSE)
9
10 Maintainer  :  libraries@haskell.org
11 Stability   :  experimental
12 Portability :  non-portable (multi-param classes, functional dependencies)
13
14 [Computation type:] Computations which read values from a shared environment.
15
16 [Binding strategy:] Monad values are functions from the environment to a value.
17 The bound function is applied to the bound value, and both have access
18 to the shared environment.
19
20 [Useful for:] Maintaining variable bindings, or other shared environment.
21
22 [Zero and plus:] None.
23
24 [Example type:] @'Reader' [(String,Value)] a@
25
26 The 'Reader' monad (also called the Environment monad).
27 Represents a computation, which can read values from
28 a shared environment, pass values from function to function,
29 and execute sub-computations in a modified environment.
30 Using 'Reader' monad for such computations is often clearer and easier
31 than using the 'Control.Monad.State.State' monad.
32
33   Inspired by the paper
34   /Functional Programming with Overloading and
35       Higher-Order Polymorphism/, 
36     Mark P Jones (<http://web.cecs.pdx.edu/~mpj/>)
37     Advanced School of Functional Programming, 1995.
38 -}
39
40 module Control.Monad.Reader.Class (
41     MonadReader(..),
42     asks,
43     ) where
44
45 import Control.Monad.Instances ()
46
47 {- |
48 See examples in "Control.Monad.Reader".
49 Note, the partially applied function type @(->) r@ is a simple reader monad.
50 See the @instance@ declaration below.
51 -}
52 class (Monad m) => MonadReader r m | m -> r where
53     -- | Retrieves the monad environment.
54     ask   :: m r
55     {- | Executes a computation in a modified environment. Parameters:
56
57     * The function to modify the environment.
58
59     * @Reader@ to run.
60
61     * The resulting @Reader@.
62     -}
63     local :: (r -> r) -> m a -> m a
64
65 -- ----------------------------------------------------------------------------
66 -- The partially applied function type is a simple reader monad
67
68 instance MonadReader r ((->) r) where
69     ask       = id
70     local f m = m . f
71
72 {- |
73 Retrieves a function of the current environment. Parameters:
74
75 * The selector function to apply to the environment.
76
77 See an example in "Control.Monad.Reader".
78 -}
79 asks :: (MonadReader r m) => (r -> a) -> m a
80 asks f = do
81     r <- ask
82     return (f r)
83