{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE StrictData #-}
module Okapi.Type where
import qualified Control.Applicative as Applicative
import qualified Control.Concurrent.Chan as Chan
import qualified Control.Concurrent.STM.TVar as TVar
import qualified Control.Monad as Monad
import qualified Control.Monad.Except as Except
import qualified Control.Monad.IO.Class as IO
import qualified Control.Monad.Morph as Morph
import qualified Control.Monad.Reader.Class as Reader
import qualified Control.Monad.State.Class as State
import qualified Control.Monad.Trans.Except as ExceptT
import qualified Control.Monad.Trans.State.Strict as StateT
import qualified Data.ByteString.Lazy as LazyByteString
import qualified Data.Text as Text
import qualified Data.Vault.Lazy as Vault
import qualified GHC.Natural as Natural
import qualified Network.HTTP.Types as HTTP
import qualified Okapi.EventSource as EventSource
type Path = [Text.Text]
type = [HTTP.Header]
type QueryItem = (Text.Text, Maybe Text.Text)
type Query = [QueryItem]
data State = State
{ State -> Request
stateRequest :: Request,
State -> Bool
stateRequestMethodParsed :: Bool,
State -> Bool
stateRequestBodyParsed :: Bool
}
data Request = Request
{ Request -> Method
requestMethod :: HTTP.Method,
Request -> Path
requestPath :: Path,
Request -> Query
requestQuery :: Query,
Request -> IO ByteString
requestBody :: IO LazyByteString.ByteString,
:: Headers,
Request -> Vault
requestVault :: Vault.Vault
}
data Result
= ResultResponse Response
| ResultFile File
| ResultEventSource EventSource.EventSource
data File = File
{ File -> Natural
fileStatus :: Natural.Natural
, :: Headers
, File -> FilePath
filePath :: FilePath
}
data Response = Response
{ Response -> Natural
responseStatus :: Natural.Natural,
:: Headers,
Response -> ByteString
responseBody :: LazyByteString.ByteString
}
data Failure = Skip | Error Response
newtype OkapiT m a = OkapiT {OkapiT m a -> ExceptT Failure (StateT State m) a
unOkapiT :: ExceptT.ExceptT Failure (StateT.StateT State m) a}
deriving newtype
( Except.MonadError Failure,
State.MonadState State
)
instance Functor m => Functor (OkapiT m) where
fmap :: (a -> b) -> OkapiT m a -> OkapiT m b
fmap :: (a -> b) -> OkapiT m a -> OkapiT m b
fmap a -> b
f OkapiT m a
okapiT =
ExceptT Failure (StateT State m) b -> OkapiT m b
forall (m :: * -> *) a.
ExceptT Failure (StateT State m) a -> OkapiT m a
OkapiT (ExceptT Failure (StateT State m) b -> OkapiT m b)
-> ((State -> m (Either Failure b, State))
-> ExceptT Failure (StateT State m) b)
-> (State -> m (Either Failure b, State))
-> OkapiT m b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StateT State m (Either Failure b)
-> ExceptT Failure (StateT State m) b
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT.ExceptT (StateT State m (Either Failure b)
-> ExceptT Failure (StateT State m) b)
-> ((State -> m (Either Failure b, State))
-> StateT State m (Either Failure b))
-> (State -> m (Either Failure b, State))
-> ExceptT Failure (StateT State m) b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (State -> m (Either Failure b, State))
-> StateT State m (Either Failure b)
forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a
StateT.StateT ((State -> m (Either Failure b, State)) -> OkapiT m b)
-> (State -> m (Either Failure b, State)) -> OkapiT m b
forall a b. (a -> b) -> a -> b
$
( ((Either Failure a, State) -> (Either Failure b, State))
-> m (Either Failure a, State) -> m (Either Failure b, State)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\ ~(Either Failure a
a, State
s') -> (a -> b
f (a -> b) -> Either Failure a -> Either Failure b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Either Failure a
a, State
s'))
(m (Either Failure a, State) -> m (Either Failure b, State))
-> (State -> m (Either Failure a, State))
-> State
-> m (Either Failure b, State)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StateT State m (Either Failure a)
-> State -> m (Either Failure a, State)
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
StateT.runStateT (ExceptT Failure (StateT State m) a
-> StateT State m (Either Failure a)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
ExceptT.runExceptT (ExceptT Failure (StateT State m) a
-> StateT State m (Either Failure a))
-> ExceptT Failure (StateT State m) a
-> StateT State m (Either Failure a)
forall a b. (a -> b) -> a -> b
$ OkapiT m a -> ExceptT Failure (StateT State m) a
forall (m :: * -> *) a.
OkapiT m a -> ExceptT Failure (StateT State m) a
unOkapiT OkapiT m a
okapiT)
)
{-# INLINE fmap #-}
instance Monad m => Applicative (OkapiT m) where
pure :: a -> OkapiT m a
pure a
x = ExceptT Failure (StateT State m) a -> OkapiT m a
forall (m :: * -> *) a.
ExceptT Failure (StateT State m) a -> OkapiT m a
OkapiT (ExceptT Failure (StateT State m) a -> OkapiT m a)
-> ((State -> m (Either Failure a, State))
-> ExceptT Failure (StateT State m) a)
-> (State -> m (Either Failure a, State))
-> OkapiT m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StateT State m (Either Failure a)
-> ExceptT Failure (StateT State m) a
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT.ExceptT (StateT State m (Either Failure a)
-> ExceptT Failure (StateT State m) a)
-> ((State -> m (Either Failure a, State))
-> StateT State m (Either Failure a))
-> (State -> m (Either Failure a, State))
-> ExceptT Failure (StateT State m) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (State -> m (Either Failure a, State))
-> StateT State m (Either Failure a)
forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a
StateT.StateT ((State -> m (Either Failure a, State)) -> OkapiT m a)
-> (State -> m (Either Failure a, State)) -> OkapiT m a
forall a b. (a -> b) -> a -> b
$ \State
s -> (Either Failure a, State) -> m (Either Failure a, State)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a -> Either Failure a
forall a b. b -> Either a b
Right a
x, State
s)
{-# INLINEABLE pure #-}
(OkapiT (ExceptT.ExceptT (StateT.StateT State -> m (Either Failure (a -> b), State)
mf))) <*> :: OkapiT m (a -> b) -> OkapiT m a -> OkapiT m b
<*> (OkapiT (ExceptT.ExceptT (StateT.StateT State -> m (Either Failure a, State)
mx))) = ExceptT Failure (StateT State m) b -> OkapiT m b
forall (m :: * -> *) a.
ExceptT Failure (StateT State m) a -> OkapiT m a
OkapiT (ExceptT Failure (StateT State m) b -> OkapiT m b)
-> ((State -> m (Either Failure b, State))
-> ExceptT Failure (StateT State m) b)
-> (State -> m (Either Failure b, State))
-> OkapiT m b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StateT State m (Either Failure b)
-> ExceptT Failure (StateT State m) b
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT.ExceptT (StateT State m (Either Failure b)
-> ExceptT Failure (StateT State m) b)
-> ((State -> m (Either Failure b, State))
-> StateT State m (Either Failure b))
-> (State -> m (Either Failure b, State))
-> ExceptT Failure (StateT State m) b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (State -> m (Either Failure b, State))
-> StateT State m (Either Failure b)
forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a
StateT.StateT ((State -> m (Either Failure b, State)) -> OkapiT m b)
-> (State -> m (Either Failure b, State)) -> OkapiT m b
forall a b. (a -> b) -> a -> b
$ \State
s -> do
~(Either Failure (a -> b)
eitherF, State
s') <- State -> m (Either Failure (a -> b), State)
mf State
s
case Either Failure (a -> b)
eitherF of
Left Failure
error -> (Either Failure b, State) -> m (Either Failure b, State)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Failure -> Either Failure b
forall a b. a -> Either a b
Left Failure
error, State
s)
Right a -> b
f -> do
~(Either Failure a
eitherX, State
s'') <- State -> m (Either Failure a, State)
mx State
s'
case Either Failure a
eitherX of
Left Failure
error' -> (Either Failure b, State) -> m (Either Failure b, State)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Failure -> Either Failure b
forall a b. a -> Either a b
Left Failure
error', State
s')
Right a
x -> (Either Failure b, State) -> m (Either Failure b, State)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (b -> Either Failure b
forall a b. b -> Either a b
Right (b -> Either Failure b) -> b -> Either Failure b
forall a b. (a -> b) -> a -> b
$ a -> b
f a
x, State
s'')
{-# INLINEABLE (<*>) #-}
OkapiT m a
m *> :: OkapiT m a -> OkapiT m b -> OkapiT m b
*> OkapiT m b
k = OkapiT m a
m OkapiT m a -> OkapiT m b -> OkapiT m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> OkapiT m b
k
{-# INLINE (*>) #-}
instance Monad m => Applicative.Alternative (OkapiT m) where
empty :: OkapiT m a
empty = ExceptT Failure (StateT State m) a -> OkapiT m a
forall (m :: * -> *) a.
ExceptT Failure (StateT State m) a -> OkapiT m a
OkapiT (ExceptT Failure (StateT State m) a -> OkapiT m a)
-> ((State -> m (Either Failure a, State))
-> ExceptT Failure (StateT State m) a)
-> (State -> m (Either Failure a, State))
-> OkapiT m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StateT State m (Either Failure a)
-> ExceptT Failure (StateT State m) a
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT.ExceptT (StateT State m (Either Failure a)
-> ExceptT Failure (StateT State m) a)
-> ((State -> m (Either Failure a, State))
-> StateT State m (Either Failure a))
-> (State -> m (Either Failure a, State))
-> ExceptT Failure (StateT State m) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (State -> m (Either Failure a, State))
-> StateT State m (Either Failure a)
forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a
StateT.StateT ((State -> m (Either Failure a, State)) -> OkapiT m a)
-> (State -> m (Either Failure a, State)) -> OkapiT m a
forall a b. (a -> b) -> a -> b
$ \State
s -> (Either Failure a, State) -> m (Either Failure a, State)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Failure -> Either Failure a
forall a b. a -> Either a b
Left Failure
Skip, State
s)
{-# INLINE empty #-}
(OkapiT (ExceptT.ExceptT (StateT.StateT State -> m (Either Failure a, State)
mx))) <|> :: OkapiT m a -> OkapiT m a -> OkapiT m a
<|> (OkapiT (ExceptT.ExceptT (StateT.StateT State -> m (Either Failure a, State)
my))) = ExceptT Failure (StateT State m) a -> OkapiT m a
forall (m :: * -> *) a.
ExceptT Failure (StateT State m) a -> OkapiT m a
OkapiT (ExceptT Failure (StateT State m) a -> OkapiT m a)
-> ((State -> m (Either Failure a, State))
-> ExceptT Failure (StateT State m) a)
-> (State -> m (Either Failure a, State))
-> OkapiT m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StateT State m (Either Failure a)
-> ExceptT Failure (StateT State m) a
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT.ExceptT (StateT State m (Either Failure a)
-> ExceptT Failure (StateT State m) a)
-> ((State -> m (Either Failure a, State))
-> StateT State m (Either Failure a))
-> (State -> m (Either Failure a, State))
-> ExceptT Failure (StateT State m) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (State -> m (Either Failure a, State))
-> StateT State m (Either Failure a)
forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a
StateT.StateT ((State -> m (Either Failure a, State)) -> OkapiT m a)
-> (State -> m (Either Failure a, State)) -> OkapiT m a
forall a b. (a -> b) -> a -> b
$ \State
s -> do
(Either Failure a
eitherX, State
stateX) <- State -> m (Either Failure a, State)
mx State
s
case Either Failure a
eitherX of
Left Failure
Skip -> do
(Either Failure a
eitherY, State
stateY) <- State -> m (Either Failure a, State)
my State
s
case Either Failure a
eitherY of
Left Failure
Skip -> (Either Failure a, State) -> m (Either Failure a, State)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Failure -> Either Failure a
forall a b. a -> Either a b
Left Failure
Skip, State
s)
Left error :: Failure
error@(Error Response
_) -> (Either Failure a, State) -> m (Either Failure a, State)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Failure -> Either Failure a
forall a b. a -> Either a b
Left Failure
error, State
s)
Right a
y -> (Either Failure a, State) -> m (Either Failure a, State)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a -> Either Failure a
forall a b. b -> Either a b
Right a
y, State
stateY)
Left error :: Failure
error@(Error Response
_) -> (Either Failure a, State) -> m (Either Failure a, State)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Failure -> Either Failure a
forall a b. a -> Either a b
Left Failure
error, State
s)
Right a
x -> (Either Failure a, State) -> m (Either Failure a, State)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a -> Either Failure a
forall a b. b -> Either a b
Right a
x, State
stateX)
{-# INLINEABLE (<|>) #-}
instance Monad m => Monad (OkapiT m) where
return :: a -> OkapiT m a
return = a -> OkapiT m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
{-# INLINEABLE return #-}
(OkapiT (ExceptT.ExceptT (StateT.StateT State -> m (Either Failure a, State)
mx))) >>= :: OkapiT m a -> (a -> OkapiT m b) -> OkapiT m b
>>= a -> OkapiT m b
f = ExceptT Failure (StateT State m) b -> OkapiT m b
forall (m :: * -> *) a.
ExceptT Failure (StateT State m) a -> OkapiT m a
OkapiT (ExceptT Failure (StateT State m) b -> OkapiT m b)
-> ((State -> m (Either Failure b, State))
-> ExceptT Failure (StateT State m) b)
-> (State -> m (Either Failure b, State))
-> OkapiT m b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StateT State m (Either Failure b)
-> ExceptT Failure (StateT State m) b
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT.ExceptT (StateT State m (Either Failure b)
-> ExceptT Failure (StateT State m) b)
-> ((State -> m (Either Failure b, State))
-> StateT State m (Either Failure b))
-> (State -> m (Either Failure b, State))
-> ExceptT Failure (StateT State m) b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (State -> m (Either Failure b, State))
-> StateT State m (Either Failure b)
forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a
StateT.StateT ((State -> m (Either Failure b, State)) -> OkapiT m b)
-> (State -> m (Either Failure b, State)) -> OkapiT m b
forall a b. (a -> b) -> a -> b
$ \State
s -> do
~(Either Failure a
eitherX, State
s') <- State -> m (Either Failure a, State)
mx State
s
case Either Failure a
eitherX of
Left Failure
error -> (Either Failure b, State) -> m (Either Failure b, State)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Failure -> Either Failure b
forall a b. a -> Either a b
Left Failure
error, State
s)
Right a
x -> do
~(Either Failure b
eitherResult, State
s'') <- StateT State m (Either Failure b)
-> State -> m (Either Failure b, State)
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
StateT.runStateT (ExceptT Failure (StateT State m) b
-> StateT State m (Either Failure b)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
ExceptT.runExceptT (ExceptT Failure (StateT State m) b
-> StateT State m (Either Failure b))
-> ExceptT Failure (StateT State m) b
-> StateT State m (Either Failure b)
forall a b. (a -> b) -> a -> b
$ OkapiT m b -> ExceptT Failure (StateT State m) b
forall (m :: * -> *) a.
OkapiT m a -> ExceptT Failure (StateT State m) a
unOkapiT (OkapiT m b -> ExceptT Failure (StateT State m) b)
-> OkapiT m b -> ExceptT Failure (StateT State m) b
forall a b. (a -> b) -> a -> b
$ a -> OkapiT m b
f a
x) State
s'
case Either Failure b
eitherResult of
Left Failure
error' -> (Either Failure b, State) -> m (Either Failure b, State)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Failure -> Either Failure b
forall a b. a -> Either a b
Left Failure
error', State
s')
Right b
res -> (Either Failure b, State) -> m (Either Failure b, State)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (b -> Either Failure b
forall a b. b -> Either a b
Right b
res, State
s'')
{-# INLINEABLE (>>=) #-}
instance Monad m => Monad.MonadPlus (OkapiT m) where
mzero :: OkapiT m a
mzero = ExceptT Failure (StateT State m) a -> OkapiT m a
forall (m :: * -> *) a.
ExceptT Failure (StateT State m) a -> OkapiT m a
OkapiT (ExceptT Failure (StateT State m) a -> OkapiT m a)
-> ((State -> m (Either Failure a, State))
-> ExceptT Failure (StateT State m) a)
-> (State -> m (Either Failure a, State))
-> OkapiT m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StateT State m (Either Failure a)
-> ExceptT Failure (StateT State m) a
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT.ExceptT (StateT State m (Either Failure a)
-> ExceptT Failure (StateT State m) a)
-> ((State -> m (Either Failure a, State))
-> StateT State m (Either Failure a))
-> (State -> m (Either Failure a, State))
-> ExceptT Failure (StateT State m) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (State -> m (Either Failure a, State))
-> StateT State m (Either Failure a)
forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a
StateT.StateT ((State -> m (Either Failure a, State)) -> OkapiT m a)
-> (State -> m (Either Failure a, State)) -> OkapiT m a
forall a b. (a -> b) -> a -> b
$ \State
s -> (Either Failure a, State) -> m (Either Failure a, State)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Failure -> Either Failure a
forall a b. a -> Either a b
Left Failure
Skip, State
s)
{-# INLINE mzero #-}
(OkapiT (ExceptT.ExceptT (StateT.StateT State -> m (Either Failure a, State)
mx))) mplus :: OkapiT m a -> OkapiT m a -> OkapiT m a
`mplus` (OkapiT (ExceptT.ExceptT (StateT.StateT State -> m (Either Failure a, State)
my))) = ExceptT Failure (StateT State m) a -> OkapiT m a
forall (m :: * -> *) a.
ExceptT Failure (StateT State m) a -> OkapiT m a
OkapiT (ExceptT Failure (StateT State m) a -> OkapiT m a)
-> ((State -> m (Either Failure a, State))
-> ExceptT Failure (StateT State m) a)
-> (State -> m (Either Failure a, State))
-> OkapiT m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StateT State m (Either Failure a)
-> ExceptT Failure (StateT State m) a
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT.ExceptT (StateT State m (Either Failure a)
-> ExceptT Failure (StateT State m) a)
-> ((State -> m (Either Failure a, State))
-> StateT State m (Either Failure a))
-> (State -> m (Either Failure a, State))
-> ExceptT Failure (StateT State m) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (State -> m (Either Failure a, State))
-> StateT State m (Either Failure a)
forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a
StateT.StateT ((State -> m (Either Failure a, State)) -> OkapiT m a)
-> (State -> m (Either Failure a, State)) -> OkapiT m a
forall a b. (a -> b) -> a -> b
$ \State
s -> do
(Either Failure a
eitherX, State
stateX) <- State -> m (Either Failure a, State)
mx State
s
case Either Failure a
eitherX of
Left Failure
Skip -> do
(Either Failure a
eitherY, State
stateY) <- State -> m (Either Failure a, State)
my State
s
case Either Failure a
eitherY of
Left Failure
Skip -> (Either Failure a, State) -> m (Either Failure a, State)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Failure -> Either Failure a
forall a b. a -> Either a b
Left Failure
Skip, State
s)
Left error :: Failure
error@(Error Response
_) -> (Either Failure a, State) -> m (Either Failure a, State)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Failure -> Either Failure a
forall a b. a -> Either a b
Left Failure
error, State
s)
Right a
y -> (Either Failure a, State) -> m (Either Failure a, State)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a -> Either Failure a
forall a b. b -> Either a b
Right a
y, State
stateY)
Left error :: Failure
error@(Error Response
_) -> (Either Failure a, State) -> m (Either Failure a, State)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Failure -> Either Failure a
forall a b. a -> Either a b
Left Failure
error, State
s)
Right a
x -> (Either Failure a, State) -> m (Either Failure a, State)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a -> Either Failure a
forall a b. b -> Either a b
Right a
x, State
stateX)
{-# INLINEABLE mplus #-}
instance IO.MonadIO m => IO.MonadIO (OkapiT m) where
liftIO :: IO a -> OkapiT m a
liftIO = m a -> OkapiT m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
Morph.lift (m a -> OkapiT m a) -> (IO a -> m a) -> IO a -> OkapiT m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
IO.liftIO
instance Reader.MonadReader r m => Reader.MonadReader r (OkapiT m) where
ask :: OkapiT m r
ask = m r -> OkapiT m r
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
Morph.lift m r
forall r (m :: * -> *). MonadReader r m => m r
Reader.ask
local :: (r -> r) -> OkapiT m a -> OkapiT m a
local = (m (Either Failure a, State) -> m (Either Failure a, State))
-> OkapiT m a -> OkapiT m a
forall a (n :: * -> *) b.
(m (Either Failure a, State) -> n (Either Failure b, State))
-> OkapiT m a -> OkapiT n b
mapOkapiT ((m (Either Failure a, State) -> m (Either Failure a, State))
-> OkapiT m a -> OkapiT m a)
-> ((r -> r)
-> m (Either Failure a, State) -> m (Either Failure a, State))
-> (r -> r)
-> OkapiT m a
-> OkapiT m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (r -> r)
-> m (Either Failure a, State) -> m (Either Failure a, State)
forall r (m :: * -> *) a. MonadReader r m => (r -> r) -> m a -> m a
Reader.local
where
mapOkapiT :: (m (Either Failure a, State) -> n (Either Failure b, State)) -> OkapiT m a -> OkapiT n b
mapOkapiT :: (m (Either Failure a, State) -> n (Either Failure b, State))
-> OkapiT m a -> OkapiT n b
mapOkapiT m (Either Failure a, State) -> n (Either Failure b, State)
f OkapiT m a
okapiT = ExceptT Failure (StateT State n) b -> OkapiT n b
forall (m :: * -> *) a.
ExceptT Failure (StateT State m) a -> OkapiT m a
OkapiT (ExceptT Failure (StateT State n) b -> OkapiT n b)
-> ((State -> n (Either Failure b, State))
-> ExceptT Failure (StateT State n) b)
-> (State -> n (Either Failure b, State))
-> OkapiT n b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StateT State n (Either Failure b)
-> ExceptT Failure (StateT State n) b
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT.ExceptT (StateT State n (Either Failure b)
-> ExceptT Failure (StateT State n) b)
-> ((State -> n (Either Failure b, State))
-> StateT State n (Either Failure b))
-> (State -> n (Either Failure b, State))
-> ExceptT Failure (StateT State n) b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (State -> n (Either Failure b, State))
-> StateT State n (Either Failure b)
forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a
StateT.StateT ((State -> n (Either Failure b, State)) -> OkapiT n b)
-> (State -> n (Either Failure b, State)) -> OkapiT n b
forall a b. (a -> b) -> a -> b
$ m (Either Failure a, State) -> n (Either Failure b, State)
f (m (Either Failure a, State) -> n (Either Failure b, State))
-> (State -> m (Either Failure a, State))
-> State
-> n (Either Failure b, State)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StateT State m (Either Failure a)
-> State -> m (Either Failure a, State)
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
StateT.runStateT (ExceptT Failure (StateT State m) a
-> StateT State m (Either Failure a)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
ExceptT.runExceptT (ExceptT Failure (StateT State m) a
-> StateT State m (Either Failure a))
-> ExceptT Failure (StateT State m) a
-> StateT State m (Either Failure a)
forall a b. (a -> b) -> a -> b
$ OkapiT m a -> ExceptT Failure (StateT State m) a
forall (m :: * -> *) a.
OkapiT m a -> ExceptT Failure (StateT State m) a
unOkapiT OkapiT m a
okapiT)
reader :: (r -> a) -> OkapiT m a
reader = m a -> OkapiT m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
Morph.lift (m a -> OkapiT m a) -> ((r -> a) -> m a) -> (r -> a) -> OkapiT m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (r -> a) -> m a
forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
Reader.reader
instance Morph.MonadTrans OkapiT where
lift :: Monad m => m a -> OkapiT m a
lift :: m a -> OkapiT m a
lift m a
action = ExceptT Failure (StateT State m) a -> OkapiT m a
forall (m :: * -> *) a.
ExceptT Failure (StateT State m) a -> OkapiT m a
OkapiT (ExceptT Failure (StateT State m) a -> OkapiT m a)
-> ((State -> m (Either Failure a, State))
-> ExceptT Failure (StateT State m) a)
-> (State -> m (Either Failure a, State))
-> OkapiT m a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StateT State m (Either Failure a)
-> ExceptT Failure (StateT State m) a
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT.ExceptT (StateT State m (Either Failure a)
-> ExceptT Failure (StateT State m) a)
-> ((State -> m (Either Failure a, State))
-> StateT State m (Either Failure a))
-> (State -> m (Either Failure a, State))
-> ExceptT Failure (StateT State m) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (State -> m (Either Failure a, State))
-> StateT State m (Either Failure a)
forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a
StateT.StateT ((State -> m (Either Failure a, State)) -> OkapiT m a)
-> (State -> m (Either Failure a, State)) -> OkapiT m a
forall a b. (a -> b) -> a -> b
$ \State
s -> do
a
result <- m a
action
(Either Failure a, State) -> m (Either Failure a, State)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a -> Either Failure a
forall a b. b -> Either a b
Right a
result, State
s)
instance Morph.MFunctor OkapiT where
hoist :: Monad m => (forall a. m a -> n a) -> OkapiT m b -> OkapiT n b
hoist :: (forall a. m a -> n a) -> OkapiT m b -> OkapiT n b
hoist forall a. m a -> n a
nat OkapiT m b
okapiT = ExceptT Failure (StateT State n) b -> OkapiT n b
forall (m :: * -> *) a.
ExceptT Failure (StateT State m) a -> OkapiT m a
OkapiT (ExceptT Failure (StateT State n) b -> OkapiT n b)
-> ((State -> n (Either Failure b, State))
-> ExceptT Failure (StateT State n) b)
-> (State -> n (Either Failure b, State))
-> OkapiT n b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StateT State n (Either Failure b)
-> ExceptT Failure (StateT State n) b
forall e (m :: * -> *) a. m (Either e a) -> ExceptT e m a
ExceptT.ExceptT (StateT State n (Either Failure b)
-> ExceptT Failure (StateT State n) b)
-> ((State -> n (Either Failure b, State))
-> StateT State n (Either Failure b))
-> (State -> n (Either Failure b, State))
-> ExceptT Failure (StateT State n) b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (State -> n (Either Failure b, State))
-> StateT State n (Either Failure b)
forall s (m :: * -> *) a. (s -> m (a, s)) -> StateT s m a
StateT.StateT ((State -> n (Either Failure b, State)) -> OkapiT n b)
-> (State -> n (Either Failure b, State)) -> OkapiT n b
forall a b. (a -> b) -> a -> b
$ (m (Either Failure b, State) -> n (Either Failure b, State)
forall a. m a -> n a
nat (m (Either Failure b, State) -> n (Either Failure b, State))
-> (State -> m (Either Failure b, State))
-> State
-> n (Either Failure b, State)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StateT State m (Either Failure b)
-> State -> m (Either Failure b, State)
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
StateT.runStateT (ExceptT Failure (StateT State m) b
-> StateT State m (Either Failure b)
forall e (m :: * -> *) a. ExceptT e m a -> m (Either e a)
ExceptT.runExceptT (ExceptT Failure (StateT State m) b
-> StateT State m (Either Failure b))
-> ExceptT Failure (StateT State m) b
-> StateT State m (Either Failure b)
forall a b. (a -> b) -> a -> b
$ OkapiT m b -> ExceptT Failure (StateT State m) b
forall (m :: * -> *) a.
OkapiT m a -> ExceptT Failure (StateT State m) a
unOkapiT OkapiT m b
okapiT))
type MonadOkapi m =
( Functor m,
Applicative m,
Applicative.Alternative m,
Monad m,
Monad.MonadPlus m,
IO.MonadIO m,
Except.MonadError Failure m,
State.MonadState State m
)