Copyright | (c) gspia 2020- |
---|---|
License | BSD |
Maintainer | gspia |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Fcf.Control.Monad
Synopsis
- data Return :: a -> Exp (m a)
- data (<*>) :: f (a -> Exp b) -> f a -> Exp (f b)
- data LiftA2 :: (a -> b -> Exp c) -> f a -> f b -> Exp (f c)
- data LiftA3 :: (a -> b -> c -> Exp d) -> f a -> f b -> f c -> Exp (f d)
- data LiftA4 :: (a -> b -> c -> d -> Exp e) -> f a -> f b -> f c -> f d -> Exp (f e)
- data LiftA5 :: (a -> b -> c -> d -> e -> Exp g) -> f a -> f b -> f c -> f d -> f e -> Exp (f g)
- data (>>=) :: m a -> (a -> Exp (m b)) -> Exp (m b)
- data (>>) :: m a -> m b -> Exp (m b)
- data MapM :: (a -> Exp (m b)) -> t a -> Exp (m (t b))
- data ForM :: t a -> (a -> Exp (m b)) -> Exp (m (t b))
- data FoldlM :: (b -> a -> Exp (m b)) -> b -> t a -> Exp (m b)
- data Traverse :: (a -> Exp (f b)) -> t a -> Exp (f (t b))
- data Sequence :: t (f a) -> Exp (f (t a))
- data Id :: a -> Exp a
- data App2 :: (a -> b -> c) -> a -> Exp (b -> c)
- data App3 :: (a -> b -> c -> d) -> a -> Exp (b -> Exp (c -> d))
- data App4 :: (a -> b -> c -> d -> e) -> a -> Exp (b -> Exp (c -> Exp (d -> e)))
- data App5 :: (a -> b -> c -> d -> e -> g) -> a -> Exp (b -> Exp (c -> Exp (d -> Exp (e -> g))))
- data Star_ :: (a -> Exp b) -> f a -> Exp (f b)
- data FoldlMHelper :: (b -> a -> Exp (m b)) -> a -> (b -> Exp (m b)) -> Exp (b -> Exp (m b))
- data ConsHelper :: (a -> Exp (f b)) -> a -> f [b] -> Exp (f [b])
- data Plus1 :: Nat -> Exp Nat
- data Plus2 :: Nat -> Exp Nat
- data Plus2M :: Nat -> Exp [Nat]
- data PureXPlusY :: Nat -> Nat -> Exp [Nat]
- data XPlusYs :: Nat -> [Nat] -> Exp [Nat]
- data XsPlusYsMonadic :: [Nat] -> [Nat] -> Exp [Nat]
Documentation
>>>
import qualified GHC.TypeLits as TL
>>>
import qualified Fcf.Combinators as C
data Return :: a -> Exp (m a) Source #
Return corresponds to the return
at Monad
or pure
of Applicative.
:kind! Eval (Return 1) :: Maybe Nat :kind! Eval (Return 1) :: Either Symbol Nat
Instances
type Eval (Return a2 :: Identity a1 -> Type) Source # | |
type Eval (Return a2 :: Tree a1 -> Type) Source # | |
type Eval (Return a2 :: Maybe a1 -> Type) Source # | |
type Eval (Return a :: [k] -> Type) Source # | |
Defined in Fcf.Control.Monad | |
type Eval (Return a2 :: Either a1 b -> Type) Source # | |
type Eval (Return a :: (k1, k2) -> Type) Source # | |
Defined in Fcf.Control.Monad | |
type Eval (Return a :: (k1, k2, k3) -> Type) Source # | |
type Eval (Return a :: (k1, k2, k3, k4) -> Type) Source # | |
data (<*>) :: f (a -> Exp b) -> f a -> Exp (f b) Source #
(*) corresponds to the value level <*>
. Note that this clashes with
the definition given at Fcf.Combinators.((*)).
Applicatives that we define include:
- Identity
- []
- Maybe
- Either
- (,)
- (,,)
- (,,,)
Example
>>>
:kind! Eval ('Identity Plus2 <*> 'Identity 5)
Eval ('Identity Plus2 <*> 'Identity 5) :: Identity Natural = 'Identity 7
>>>
:kind! Eval ( (<*>) '[ (Fcf.+) 1, (Fcf.*) 10] '[4,5,6,7])
Eval ( (<*>) '[ (Fcf.+) 1, (Fcf.*) 10] '[4,5,6,7]) :: [Natural] = '[5, 6, 7, 8, 40, 50, 60, 70]>>>
:kind! Eval ( (<*>) '[ (Fcf.+) 1, (Fcf.*) 10] '[])
Eval ( (<*>) '[ (Fcf.+) 1, (Fcf.*) 10] '[]) :: [Natural] = '[]>>>
:kind! Eval ( (<*>) '[] '[4,5,6,7])
Eval ( (<*>) '[] '[4,5,6,7]) :: [b] = '[]
Instances
type Eval ('Identity f <*> m :: Identity b -> Type) Source # | |
type Eval ('Node f tfs <*> 'Node x txs :: Tree b -> Type) Source # | |
type Eval ('Just f <*> m :: Maybe b -> Type) Source # | |
type Eval (('Nothing :: Maybe (a -> Exp b)) <*> _1 :: Maybe b -> Type) Source # | |
type Eval (('[] :: [a -> Exp b]) <*> _1 :: [b] -> Type) Source # | |
Defined in Fcf.Control.Monad | |
type Eval (_1 <*> ('[] :: [a]) :: [b] -> Type) Source # | |
Defined in Fcf.Control.Monad | |
type Eval ((f ': fs) <*> (a2 ': as) :: [b] -> Type) Source # | |
type Eval (('Left e :: Either a1 (a2 -> Exp b)) <*> _1 :: Either a1 b -> Type) Source # | |
type Eval (('Right f :: Either a1 (a2 -> Exp b)) <*> m :: Either a1 b -> Type) Source # | |
type Eval ('(u, f) <*> '(v, x) :: (k1, k2) -> Type) Source # | For tuples, the
|
type Eval ('(a2, b, f) <*> '(a', b', x) :: (k1, k2, k3) -> Type) Source # | |
type Eval ('(a2, b, c, f) <*> '(a', b', c', x) :: (k1, k2, k3, k4) -> Type) Source # | |
data LiftA2 :: (a -> b -> Exp c) -> f a -> f b -> Exp (f c) Source #
Type level LiftA2.
Example
>>>
:kind! Eval (LiftA2 (Fcf.+) '[1,2] '[3,4])
Eval (LiftA2 (Fcf.+) '[1,2] '[3,4]) :: [Natural] = '[4, 5, 5, 6]
data LiftA3 :: (a -> b -> c -> Exp d) -> f a -> f b -> f c -> Exp (f d) Source #
Type level LiftA3.
Example
>>>
:kind! Eval (LiftA3 Tuple3 '[1,2] '[3,4] '[5,6])
Eval (LiftA3 Tuple3 '[1,2] '[3,4] '[5,6]) :: [(Natural, Natural, Natural)] = '[ '(1, 3, 5), '(1, 3, 6), '(1, 4, 5), '(1, 4, 6), '(2, 3, 5), '(2, 3, 6), '(2, 4, 5), '(2, 4, 6)]
>>>
:kind! Eval (LiftA3 Tuple3 ('Right 5) ('Right 6) ('Left "fail"))
Eval (LiftA3 Tuple3 ('Right 5) ('Right 6) ('Left "fail")) :: Either TL.Symbol (Natural, Natural, c) = 'Left "fail"
data LiftA4 :: (a -> b -> c -> d -> Exp e) -> f a -> f b -> f c -> f d -> Exp (f e) Source #
Type level LiftA4.
data LiftA5 :: (a -> b -> c -> d -> e -> Exp g) -> f a -> f b -> f c -> f d -> f e -> Exp (f g) Source #
Type level LiftA5.
data (>>=) :: m a -> (a -> Exp (m b)) -> Exp (m b) Source #
Type level Bind corresponding to the value level bind >>=
operator.
Note that name (>>=) clashes with the definition given at
Fcf.Combinators.(>>=). (It doesn't export it yet, though.)
Monads that we define include:
- Identity
- []
- Maybe
- Either
- (,)
- (,,)
- (,,,)
Example
Example: double the length of the input list and increase the numbers at the same time.
>>>
:kind! Eval ('[5,6,7] >>= Plus2M)
Eval ('[5,6,7] >>= Plus2M) :: [Natural] = '[7, 8, 8, 9, 9, 10]
>>>
:kind! Eval (XsPlusYsMonadic '[1,2,3] '[4,5,6])
Eval (XsPlusYsMonadic '[1,2,3] '[4,5,6]) :: [Natural] = '[5, 6, 7, 6, 7, 8, 7, 8, 9]
Instances
type Eval ('Identity a2 >>= f :: Identity b -> Type) Source # | |
type Eval (('Nothing :: Maybe a) >>= f :: Maybe b -> Type) Source # | |
type Eval ('Just a2 >>= f :: Maybe b -> Type) Source # | |
type Eval ((x ': xs) >>= f :: [b] -> Type) Source # | |
type Eval (('[] :: [a]) >>= _1 :: [b] -> Type) Source # | |
Defined in Fcf.Control.Monad | |
type Eval (('Left a3 :: Either a1 a2) >>= _1 :: Either a1 b -> Type) Source # | |
type Eval (('Right a3 :: Either a1 a2) >>= f :: Either a1 b -> Type) Source # | |
type Eval ('(u, a2) >>= k2 :: (k1, b) -> Type) Source # | |
type Eval ('(u, v, a2) >>= k3 :: (k1, k2, b) -> Type) Source # | |
type Eval ('(u, v, w, a2) >>= k4 :: (k1, k2, k3, b) -> Type) Source # | |
data (>>) :: m a -> m b -> Exp (m b) Source #
Type level >>
Example
>>>
:kind! Eval ( 'Just 1 >> 'Just 2)
Eval ( 'Just 1 >> 'Just 2) :: Maybe Natural = 'Just 2>>>
:kind! Eval ( 'Nothing >> 'Just 2)
Eval ( 'Nothing >> 'Just 2) :: Maybe Natural = 'Nothing
data MapM :: (a -> Exp (m b)) -> t a -> Exp (m (t b)) Source #
MapM
Example
>>>
:kind! Eval (MapM (ConstFn '[ 'True, 'False]) '["a","b","c"])
Eval (MapM (ConstFn '[ 'True, 'False]) '["a","b","c"]) :: [[Bool]] = '[ '[ 'True, 'True, 'True], '[ 'True, 'True, 'False], '[ 'True, 'False, 'True], '[ 'True, 'False, 'False], '[ 'False, 'True, 'True], '[ 'False, 'True, 'False], '[ 'False, 'False, 'True], '[ 'False, 'False, 'False]]
data FoldlM :: (b -> a -> Exp (m b)) -> b -> t a -> Exp (m b) Source #
FoldlM
Example
>>>
import GHC.TypeLits as TL (Symbol, type (-))
>>>
data Lambda :: Nat -> Nat -> Exp (Either Symbol Natural)
>>>
type instance Eval (Lambda a b) = If (Eval (a >= b)) ('Right (a TL.- b)) ('Left "Nat cannot be negative")
>>>
:kind! Eval (FoldlM Lambda 5 '[1,1,1])
Eval (FoldlM Lambda 5 '[1,1,1]) :: Either Symbol Natural = 'Right 2>>>
:kind! Eval (FoldlM Lambda 5 '[1,4,1])
Eval (FoldlM Lambda 5 '[1,4,1]) :: Either Symbol Natural = 'Left "Nat cannot be negative"
data Traverse :: (a -> Exp (f b)) -> t a -> Exp (f (t b)) Source #
Traverse
Example
>>>
:kind! Eval (Traverse Id '[ '[1,2], '[3,4]])
Eval (Traverse Id '[ '[1,2], '[3,4]]) :: [[Natural]] = '[ '[1, 3], '[1, 4], '[2, 3], '[2, 4]]
Instances
type Eval (Traverse f2 ('Right x :: Either a1 a3) :: f1 (Either a1 a2) -> Type) Source # | |
type Eval (Traverse f2 ('Left e :: Either a1 a2) :: f1 (Either a1 b) -> Type) Source # | |
type Eval (Traverse f2 ('Node x ts) :: f1 (Tree b) -> Type) Source # | |
type Eval (Traverse f2 ('Just x) :: f1 (Maybe a1) -> Type) Source # | |
type Eval (Traverse f2 ('Nothing :: Maybe a) :: f1 (Maybe b) -> Type) Source # | |
type Eval (Traverse f2 '(x, y) :: f1 (a1, a2) -> Type) Source # | |
type Eval (Traverse f2 lst :: f1 [b] -> Type) Source # | |
Defined in Fcf.Control.Monad |
data Sequence :: t (f a) -> Exp (f (t a)) Source #
Sequence
Example
>>>
:kind! Eval (Sequence ('Just ('Right 5)))
Eval (Sequence ('Just ('Right 5))) :: Either a (Maybe Natural) = 'Right ('Just 5)
>>>
:kind! Eval (Sequence '[ 'Just 3, 'Just 5, 'Just 7])
Eval (Sequence '[ 'Just 3, 'Just 5, 'Just 7]) :: Maybe [Natural] = 'Just '[3, 5, 7]
>>>
:kind! Eval (Sequence '[ 'Just 3, 'Nothing, 'Just 7])
Eval (Sequence '[ 'Just 3, 'Nothing, 'Just 7]) :: Maybe [Natural] = 'Nothing
>>>
:kind! Eval (Sequence '[ '[1,2], '[3,4]])
Eval (Sequence '[ '[1,2], '[3,4]]) :: [[Natural]] = '[ '[1, 3], '[1, 4], '[2, 3], '[2, 4]]
data App2 :: (a -> b -> c) -> a -> Exp (b -> c) Source #
Needed by LiftA2 instance to partially apply function
data App3 :: (a -> b -> c -> d) -> a -> Exp (b -> Exp (c -> d)) Source #
Needed by LiftA3 instance to partially apply function
data App4 :: (a -> b -> c -> d -> e) -> a -> Exp (b -> Exp (c -> Exp (d -> e))) Source #
Needed by LiftA4 instance to partially apply function
data App5 :: (a -> b -> c -> d -> e -> g) -> a -> Exp (b -> Exp (c -> Exp (d -> Exp (e -> g)))) Source #
Needed by LiftA5 instance to partially apply function
data Star_ :: (a -> Exp b) -> f a -> Exp (f b) Source #
Helper for the [] applicative instance.
data FoldlMHelper :: (b -> a -> Exp (m b)) -> a -> (b -> Exp (m b)) -> Exp (b -> Exp (m b)) Source #
Helper for FoldlM
data ConsHelper :: (a -> Exp (f b)) -> a -> f [b] -> Exp (f [b]) Source #
Helper for [] traverse
Instances
type Eval (ConsHelper f2 x ys :: f1 [a1] -> Type) Source # | |
Defined in Fcf.Control.Monad |
data Plus2M :: Nat -> Exp [Nat] Source #
For the example. Turn an input number to list of two numbers of a bit larger numbers.
data XsPlusYsMonadic :: [Nat] -> [Nat] -> Exp [Nat] Source #
An example implementing
sumM xs ys = do x <- xs y <- ys return (x + y)
or
sumM xs ys = xs >>= (x -> ys >>= (y -> pure (x+y)))
Note the use of helper functions. This is a bit awkward, a type level lambda would be nice.
Instances
type Eval (XsPlusYsMonadic xs ys :: [Nat] -> Type) Source # | |
Defined in Fcf.Control.Monad |