script-monad-0.0.4: Stack of error, reader, writer, state, and prompt monad transformers
Copyright2018 Automattic Inc.
LicenseBSD3
MaintainerNathan Bloomfield (nbloomf@gmail.com)
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Control.Monad.Script.Http

Description

A basic type and monad transformer transformer for describing HTTP interactions.

Synopsis

HttpT

type HttpT e r w s p = HttpTT e r w s p IdentityT Source #

An HTTP session returning an a, writing to a log of type W e w, reading from an environment of type R e w r, with state of type S s, throwing errors of type E e, performing effectful computations described by P p a, with inner monad eff. HttpTT over IdentityT.

HttpT

data HttpTT e r w s p t eff a Source #

An HTTP session returning an a, writing to a log of type W e w, reading from an environment of type R e w r, with state of type S s, throwing errors of type E e, performing effectful computations described by P p a, and with inner monad t eff.

Instances

Instances details
(MonadTrans t, forall (m :: Type -> Type). Monad m => Monad (t m)) => MonadTrans (HttpTT e r w s p t) Source # 
Instance details

Defined in Control.Monad.Script.Http

Methods

lift :: Monad m => m a -> HttpTT e r w s p t m a #

(Monad eff, Monad (t eff), MonadTrans t) => Monad (HttpTT e r w s p t eff) Source # 
Instance details

Defined in Control.Monad.Script.Http

Methods

(>>=) :: HttpTT e r w s p t eff a -> (a -> HttpTT e r w s p t eff b) -> HttpTT e r w s p t eff b #

(>>) :: HttpTT e r w s p t eff a -> HttpTT e r w s p t eff b -> HttpTT e r w s p t eff b #

return :: a -> HttpTT e r w s p t eff a #

(Monad eff, Monad (t eff), MonadTrans t) => Functor (HttpTT e r w s p t eff) Source # 
Instance details

Defined in Control.Monad.Script.Http

Methods

fmap :: (a -> b) -> HttpTT e r w s p t eff a -> HttpTT e r w s p t eff b #

(<$) :: a -> HttpTT e r w s p t eff b -> HttpTT e r w s p t eff a #

(Monad eff, Monad (t eff), MonadTrans t, MonadFail (t eff)) => MonadFail (HttpTT e r w s p t eff) Source # 
Instance details

Defined in Control.Monad.Script.Http

Methods

fail :: String -> HttpTT e r w s p t eff a #

(Monad eff, Monad (t eff), MonadTrans t) => Applicative (HttpTT e r w s p t eff) Source # 
Instance details

Defined in Control.Monad.Script.Http

Methods

pure :: a -> HttpTT e r w s p t eff a #

(<*>) :: HttpTT e r w s p t eff (a -> b) -> HttpTT e r w s p t eff a -> HttpTT e r w s p t eff b #

liftA2 :: (a -> b -> c) -> HttpTT e r w s p t eff a -> HttpTT e r w s p t eff b -> HttpTT e r w s p t eff c #

(*>) :: HttpTT e r w s p t eff a -> HttpTT e r w s p t eff b -> HttpTT e r w s p t eff b #

(<*) :: HttpTT e r w s p t eff a -> HttpTT e r w s p t eff b -> HttpTT e r w s p t eff a #

execHttpTT Source #

Arguments

:: (Monad eff, Monad (t eff), MonadTrans t) 
=> S s

Initial state

-> R e w r

Environment

-> (forall u. P p u -> eff u)

Effect evaluator

-> HttpTT e r w s p t eff a 
-> t eff (Either (E e) a, S s, W e w) 

Execute an HttpTT session.

liftHttpTT :: (Monad eff, Monad (t eff), MonadTrans t) => t eff a -> HttpTT e r w s p t eff a Source #

Lift a value from the inner transformer.

Error

throwError :: (Monad eff, Monad (t eff), MonadTrans t) => e -> HttpTT e r w s p t eff a Source #

Also logs the exception.

throwJsonError :: (Monad eff, Monad (t eff), MonadTrans t) => JsonError -> HttpTT e r w s p t eff a Source #

Also logs the exception.

throwHttpException :: (Monad eff, Monad (t eff), MonadTrans t) => HttpException -> HttpTT e r w s p t eff a Source #

Also logs the exception.

throwIOException :: (Monad eff, Monad (t eff), MonadTrans t) => IOException -> HttpTT e r w s p t eff a Source #

Also logs the exception.

catchError Source #

Arguments

:: (Monad eff, Monad (t eff), MonadTrans t) 
=> HttpTT e r w s p t eff a 
-> (e -> HttpTT e r w s p t eff a)

Handler

-> HttpTT e r w s p t eff a 

Re-throws other error types.

catchJsonError Source #

Arguments

:: (Monad eff, Monad (t eff), MonadTrans t) 
=> HttpTT e r w s p t eff a 
-> (JsonError -> HttpTT e r w s p t eff a)

Handler

-> HttpTT e r w s p t eff a 

Re-throws other error types.

catchHttpException Source #

Arguments

:: (Monad eff, Monad (t eff), MonadTrans t) 
=> HttpTT e r w s p t eff a 
-> (HttpException -> HttpTT e r w s p t eff a)

Handler

-> HttpTT e r w s p t eff a 

Re-throws other error types.

catchIOException Source #

Arguments

:: (Monad eff, Monad (t eff), MonadTrans t) 
=> HttpTT e r w s p t eff a 
-> (IOException -> HttpTT e r w s p t eff a)

Handler

-> HttpTT e r w s p t eff a 

Re-throws other error types.

catchAnyError :: (Monad eff, Monad (t eff), MonadTrans t) => HttpTT e r w s p t eff a -> (e -> HttpTT e r w s p t eff a) -> (HttpException -> HttpTT e r w s p t eff a) -> (IOException -> HttpTT e r w s p t eff a) -> (JsonError -> HttpTT e r w s p t eff a) -> HttpTT e r w s p t eff a Source #

Handle any thrown error. To handle only errors of a specific type, see catchError, catchJsonError, catchIOException, or catchHttpException.

printError :: (e -> Text) -> E e -> Text Source #

Pretty printer for errors

data E e Source #

Error type.

Constructors

E_Http HttpException 
E_IO IOException 
E_Json JsonError 
E e

Client-supplied error type.

Instances

Instances details
Show e => Show (E e) Source # 
Instance details

Defined in Control.Monad.Script.Http

Methods

showsPrec :: Int -> E e -> ShowS #

show :: E e -> String #

showList :: [E e] -> ShowS #

Reader

ask :: (Monad eff, Monad (t eff), MonadTrans t) => HttpTT e r w s p t eff (R e w r) Source #

Retrieve the environment.

local :: (Monad eff, Monad (t eff), MonadTrans t) => (R e w r -> R e w r) -> HttpTT e r w s p t eff a -> HttpTT e r w s p t eff a Source #

Run an action with a locally adjusted environment of the same type.

reader :: (Monad eff, Monad (t eff), MonadTrans t) => (R e w r -> a) -> HttpTT e r w s p t eff a Source #

Retrieve the image of the environment under a given function.

data R e w r Source #

Generic session environment.

Constructors

R 

Fields

basicEnv Source #

Arguments

:: (Show e, Show w) 
=> r

Client-supplied environment value.

-> R e w r 

Environment constructor

trivialEnv Source #

Arguments

:: r

Client-supplied environment value.

-> R e w r 

Environment constructor

data LogOptions e w Source #

Options for tweaking the logs.

Constructors

LogOptions 

Fields

basicLogOptions :: (Show e, Show w) => LogOptions e w Source #

Noisy, in color, without parsing JSON responses, and using Show instances for user-supplied error and log types.

trivialLogOptions :: LogOptions e w Source #

Noisy, in color, without parsing JSON responses, and using trivial printers for user-supplied error and log types. For testing.

Writer

logEntries :: W e w -> [w] Source #

Extract the user-defined log entries.

data LogSeverity Source #

Syslog style log severities.

Constructors

LogDebug

Debug-level messages

LogInfo

Informational messages

LogNotice

Normal but significant condition

LogWarning

Warning conditions

LogError

Error conditions

LogCritical

Critical conditions

LogAlert

Action must be taken immediately

LogEmergency

System is unusable

setLogSeverity :: (Monad eff, Monad (t eff), MonadTrans t) => LogSeverity -> HttpTT e r w s p t eff a -> HttpTT e r w s p t eff a Source #

Set the severity level of all log actions in a session.

data W e w Source #

Log type

Instances

Instances details
(Show e, Show w) => Show (W e w) Source # 
Instance details

Defined in Control.Monad.Script.Http

Methods

showsPrec :: Int -> W e w -> ShowS #

show :: W e w -> String #

showList :: [W e w] -> ShowS #

Semigroup (W e w) Source # 
Instance details

Defined in Control.Monad.Script.Http

Methods

(<>) :: W e w -> W e w -> W e w #

sconcat :: NonEmpty (W e w) -> W e w #

stimes :: Integral b => b -> W e w -> W e w #

Monoid (W e w) Source # 
Instance details

Defined in Control.Monad.Script.Http

Methods

mempty :: W e w #

mappend :: W e w -> W e w -> W e w #

mconcat :: [W e w] -> W e w #

printHttpLogs :: Handle -> Maybe (MVar ()) -> LogOptions e w -> (LogOptions e w -> LogEntry e w -> Maybe Text) -> W e w -> IO () Source #

All log statements should go through logNow.

basicLogEntryPrinter :: LogOptions e w -> LogEntry e w -> Maybe Text Source #

Simple default pretty printer for LogEntrys.

State

gets :: (Monad eff, Monad (t eff), MonadTrans t) => (S s -> a) -> HttpTT e r w s p t eff a Source #

Retrieve the image of the current state under a given function.

modify :: (Monad eff, Monad (t eff), MonadTrans t) => (S s -> S s) -> HttpTT e r w s p t eff () Source #

Modify the current state strictly.

data S s Source #

State type

Constructors

S 

Instances

Instances details
Show s => Show (S s) Source # 
Instance details

Defined in Control.Monad.Script.Http

Methods

showsPrec :: Int -> S s -> ShowS #

show :: S s -> String #

showList :: [S s] -> ShowS #

basicState :: s -> S s Source #

State constructor

Prompt

prompt :: (Monad eff, Monad (t eff), MonadTrans t) => P p a -> HttpTT e r w s p t eff a Source #

Inject an atomic effect.

evalIO Source #

Arguments

:: (p a -> IO a)

Evaluator for user effects

-> P p a 
-> IO a 

Basic evaluator for interpreting atomic Http effects in IO.

evalMockIO :: (p a -> MockIO s a) -> P p a -> MockIO s a Source #

Basic evaluator for interpreting atomic Http effects in MockIO.

API

comment :: (Monad eff, Monad (t eff), MonadTrans t) => Text -> HttpTT e r w s p t eff () Source #

Write a comment to the log

wait Source #

Arguments

:: (Monad eff, Monad (t eff), MonadTrans t) 
=> Int

milliseconds

-> HttpTT e r w s p t eff () 

Pause the thread

logDebug :: (Monad eff, Monad (t eff), MonadTrans t) => w -> HttpTT e r w s p t eff () Source #

For debug level messages

logInfo :: (Monad eff, Monad (t eff), MonadTrans t) => w -> HttpTT e r w s p t eff () Source #

For informational messages

logNotice :: (Monad eff, Monad (t eff), MonadTrans t) => w -> HttpTT e r w s p t eff () Source #

For normal but significant conditions

logWarning :: (Monad eff, Monad (t eff), MonadTrans t) => w -> HttpTT e r w s p t eff () Source #

For warning conditions

logError :: (Monad eff, Monad (t eff), MonadTrans t) => w -> HttpTT e r w s p t eff () Source #

For error conditions

logCritical :: (Monad eff, Monad (t eff), MonadTrans t) => w -> HttpTT e r w s p t eff () Source #

For critical conditions

logAlert :: (Monad eff, Monad (t eff), MonadTrans t) => w -> HttpTT e r w s p t eff () Source #

Action must be taken immediately

logEmergency :: (Monad eff, Monad (t eff), MonadTrans t) => w -> HttpTT e r w s p t eff () Source #

System is unusable

IO

hPutStrLn :: (Monad eff, Monad (t eff), MonadTrans t) => Handle -> Text -> HttpTT e r w s p t eff () Source #

Write a line to a handle

hPutStrLnBlocking :: (Monad eff, Monad (t eff), MonadTrans t) => MVar () -> Handle -> Text -> HttpTT e r w s p t eff () Source #

Write a line to a handle, using the given MVar as a lock

HTTP calls

httpGet :: (Monad eff, Monad (t eff), MonadTrans t) => Url -> HttpTT e r w s p t eff HttpResponse Source #

Run a GET request

httpSilentGet :: (Monad eff, Monad (t eff), MonadTrans t) => Url -> HttpTT e r w s p t eff HttpResponse Source #

Run a GET request, but do not write the request or response to the logs.

httpPost Source #

Arguments

:: (Monad eff, Monad (t eff), MonadTrans t) 
=> Url 
-> ByteString

Payload

-> HttpTT e r w s p t eff HttpResponse 

Run a POST request

httpSilentPost Source #

Arguments

:: (Monad eff, Monad (t eff), MonadTrans t) 
=> Url 
-> ByteString

Payload

-> HttpTT e r w s p t eff HttpResponse 

Run a POST request, but do not write the request or response to the logs.

httpDelete :: (Monad eff, Monad (t eff), MonadTrans t) => Url -> HttpTT e r w s p t eff HttpResponse Source #

Run a DELETE request

httpSilentDelete :: (Monad eff, Monad (t eff), MonadTrans t) => Url -> HttpTT e r w s p t eff HttpResponse Source #

Run a DELETE request, but do not write the request or response to the logs.

JSON

parseJson :: (Monad eff, Monad (t eff), MonadTrans t) => ByteString -> HttpTT e r w s p t eff Value Source #

Parse a ByteString to a JSON Value.

lookupKeyJson Source #

Arguments

:: (Monad eff, Monad (t eff), MonadTrans t) 
=> Text

Key name

-> Value

JSON object

-> HttpTT e r w s p t eff Value 

Object member lookup.

constructFromJson :: (Monad eff, Monad (t eff), MonadTrans t, FromJSON a) => Value -> HttpTT e r w s p t eff a Source #

Decode a Value to some other type.

Types

type Url = Text Source #

To make type signatures nicer

data JsonError Source #

Represents the kinds of errors that can occur when parsing and decoding JSON.

Constructors

JsonError Text

A generic JSON error; try not to use this.

JsonParseError ByteString

A failed parse.

JsonKeyDoesNotExist Text Value

An attempt to look up the value of a key that does not exist on an object.

JsonKeyLookupOffObject Text Value

An attempt to look up the value of a key on something other than an object.

JsonConstructError String

A failed attempt to convert a Value to some other type.

Instances

Instances details
Eq JsonError Source # 
Instance details

Defined in Data.Aeson.Extras

Show JsonError Source # 
Instance details

Defined in Data.Aeson.Extras

Arbitrary JsonError Source # 
Instance details

Defined in Data.Aeson.Extras

Testing

checkHttpTT Source #

Arguments

:: forall eff t q e r w s p a prop. (Monad eff, Monad (t eff), MonadTrans t, Show q, Testable prop) 
=> S s

Initial state

-> R e w r

Environment

-> (forall u. P p u -> eff u)

Effect evaluator

-> (t eff (Either (E e) a, S s, W e w) -> IO q)

Condense to IO

-> (q -> prop)

Result check

-> HttpTT e r w s p t eff a 
-> Property 

Turn an HttpTT into a property; for testing with QuickCheck.