{-# LANGUAGE TypeOperators, FlexibleContexts, FlexibleInstances, MultiParamTypeClasses, UndecidableInstances, Rank2Types #-}
module Control.Ev.Util
(
Reader(Reader,ask)
, reader
, State(State,get,put)
, state
, Writer(Writer,tell)
, writer
, Except(Except,throwError)
, catchError, exceptEither, exceptMaybe, exceptDefault
, Choose(Choose,none,choose)
, chooseFirst, chooseAll
) where
import Control.Ev.Eff
import Control.Monad
import Control.Applicative
data Reader a e ans = Reader { ask :: !(Op () a e ans)
}
{-# INLINE reader #-}
reader :: a -> Eff (Reader a :* e) ans -> Eff e ans
reader x
= handler (Reader{ ask = value x })
data State a e ans = State { get :: !(Op () a e ans)
, put :: !(Op a () e ans)
}
{-# INLINE state #-}
state :: a -> Eff (State a :* e) ans -> Eff e ans
state init
= handlerLocal init (State{ get = function (\_ -> localGet),
put = function (\x -> localPut x) })
data Writer a e ans = Writer { tell :: !(Op a () e ans)
}
{-# INLINE writer #-}
writer :: (Monoid a) => Eff (Writer a :* e) ans -> Eff e (ans,a)
writer
= handlerLocalRet mempty (,) $
Writer{ tell = function (\x -> do{ xs <- localGet; localPut (mappend xs x); return () }) }
data Except a e ans = Except { throwError :: !(forall b. Op a b e ans)
}
catchError :: Eff (Except a :* e) ans -> (a -> Eff e ans) -> Eff e ans
catchError action h
= handler (Except{ throwError = except (\x -> h x) }) action
exceptEither :: Eff (Except a :* e) ans -> Eff e (Either a ans)
exceptEither
= handlerRet Right (Except{ throwError = except (\x -> return (Left x) ) })
exceptDefault :: ans -> Eff (Except a :* e) ans -> Eff e ans
exceptDefault def
= handler (Except{ throwError = except (\_ -> return def) })
exceptMaybe :: Eff (Except a :* e) ans -> Eff e (Maybe ans)
exceptMaybe
= handlerRet Just (Except{ throwError = except (\_ -> return Nothing) })
data Choose e ans = Choose { none :: !(forall a. Op () a e ans)
, choose :: !(Op Int Int e ans)
}
chooseFirst :: Eff (Choose :* e) ans -> Eff e (Maybe ans)
chooseFirst
= handlerRet Just $
Choose{ none = except (\_ -> return Nothing)
, choose = operation (\hi k -> let try n = if (n > hi)
then return Nothing
else do x <- k n
case x of
Nothing -> try (n+1)
_ -> return x
in try 1)
}
chooseAll :: Eff (Choose :* e) a -> Eff e [a]
chooseAll
= handlerRet (\x -> [x]) $
Choose{ none = except (\_ -> return [])
, choose = operation (\hi k -> let collect 0 acc = return acc
collect n acc = do xs <- k n
collect (n-1) $! (xs ++ acc)
in collect hi [])
}
instance (Choose :? e) => Alternative (Eff e) where
empty = perform none ()
m1 <|> m2 = do x <- perform choose 2
if (x==1) then m1 else m2
instance (Choose :? e) => MonadPlus (Eff e) where
mzero = perform none ()
mplus m1 m2 = do x <- perform choose 2
if (x==1) then m1 else m2