script-monad-0.0.1: Transformer stack of error, reader, writer, state, and prompt monads

Copyright2018 Automattic Inc.
LicenseBSD3
MaintainerNathan Bloomfield (nbloomf@gmail.com)
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Control.Monad.Script.Http

Contents

Description

A basic type and monad for describing HTTP interactions.

Synopsis

Http

type Http e r w s p a = HttpT e r w s p Identity 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. HttpT over Identity.

execHttpM Source #

Arguments

:: Monad eff 
=> S s

Initial state

-> R e w r

Environment

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

Effect evaluator

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

Execute an Http session.

HttpT

data HttpT e r w s p m 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 m.

Instances

Monad (HttpT e r w s p m) Source # 

Methods

(>>=) :: HttpT e r w s p m a -> (a -> HttpT e r w s p m b) -> HttpT e r w s p m b #

(>>) :: HttpT e r w s p m a -> HttpT e r w s p m b -> HttpT e r w s p m b #

return :: a -> HttpT e r w s p m a #

fail :: String -> HttpT e r w s p m a #

Functor (HttpT e r w s p m) Source # 

Methods

fmap :: (a -> b) -> HttpT e r w s p m a -> HttpT e r w s p m b #

(<$) :: a -> HttpT e r w s p m b -> HttpT e r w s p m a #

Applicative (HttpT e r w s p m) Source # 

Methods

pure :: a -> HttpT e r w s p m a #

(<*>) :: HttpT e r w s p m (a -> b) -> HttpT e r w s p m a -> HttpT e r w s p m b #

liftA2 :: (a -> b -> c) -> HttpT e r w s p m a -> HttpT e r w s p m b -> HttpT e r w s p m c #

(*>) :: HttpT e r w s p m a -> HttpT e r w s p m b -> HttpT e r w s p m b #

(<*) :: HttpT e r w s p m a -> HttpT e r w s p m b -> HttpT e r w s p m a #

execHttpTM Source #

Arguments

:: (Monad (m eff), Monad eff) 
=> S s

Initial state

-> R e w r

Environment

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

Effect evaluator

-> (forall u. eff u -> m eff u)

Lift effects to the inner monad

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

Execute an HttpT session.

liftHttpT :: Monad m => m a -> HttpT e r w s p m a Source #

Lift a value from the inner monad

Error

throwError :: e -> HttpT e r w s p m a Source #

Also logs the exception.

throwJsonError :: JsonError -> HttpT e r w s p m a Source #

Also logs the exception.

throwHttpException :: HttpException -> HttpT e r w s p m a Source #

Also logs the exception.

throwIOException :: IOException -> HttpT e r w s p m a Source #

Also logs the exception.

catchError Source #

Arguments

:: HttpT e r w s p m a 
-> (e -> HttpT e r w s p m a)

Handler

-> HttpT e r w s p m a 

Re-throws other error types.

catchJsonError Source #

Arguments

:: HttpT e r w s p m a 
-> (JsonError -> HttpT e r w s p m a)

Handler

-> HttpT e r w s p m a 

Re-throws other error types.

catchHttpException Source #

Arguments

:: HttpT e r w s p m a 
-> (HttpException -> HttpT e r w s p m a)

Handler

-> HttpT e r w s p m a 

Re-throws other error types.

catchIOException Source #

Arguments

:: HttpT e r w s p m a 
-> (IOException -> HttpT e r w s p m a)

Handler

-> HttpT e r w s p m a 

Re-throws other error types.

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

Pretty printer for errors

data E e Source #

Error type.

Reader

ask :: HttpT e r w s p m (R e w r) Source #

Retrieve the environment.

local :: (R e w r -> R e w r) -> HttpT e r w s p m a -> HttpT e r w s p m a Source #

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

reader :: (R e w r -> a) -> HttpT e r w s p m 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 W e w Source #

Log type

Instances

Monoid (W e w) Source # 

Methods

mempty :: W e w #

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

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

State

gets :: (S s -> a) -> HttpT e r w s p m a Source #

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

modify :: (S s -> S s) -> HttpT e r w s p m () Source #

Modify the current state strictly.

data S s Source #

State type

Constructors

S 

basicState :: s -> S s Source #

State constructor

Prompt

prompt :: P p a -> HttpT e r w s p m 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 :: String -> HttpT e r w s p m () Source #

Write a comment to the log

wait Source #

Arguments

:: Int

milliseconds

-> HttpT e r w s p m () 

Pause the thread

logEntry :: w -> HttpT e r w s p m () Source #

Write an entry to the log

IO

hPutStrLn :: Handle -> String -> HttpT e r w s p m () Source #

Write a line to a handle

hPutStrLnBlocking :: MVar () -> Handle -> String -> HttpT e r w s p m () Source #

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

HTTP calls

httpGet :: Url -> HttpT e r w s p m HttpResponse Source #

Run a GET request

httpSilentGet :: Url -> HttpT e r w s p m HttpResponse Source #

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

httpPost Source #

Arguments

:: Url 
-> ByteString

Payload

-> HttpT e r w s p m HttpResponse 

Run a POST request

httpSilentPost Source #

Arguments

:: Url 
-> ByteString

Payload

-> HttpT e r w s p m HttpResponse 

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

httpDelete :: Url -> HttpT e r w s p m HttpResponse Source #

Run a DELETE request

httpSilentDelete :: Url -> HttpT e r w s p m HttpResponse Source #

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

JSON

parseJson :: ByteString -> HttpT e r w s p m Value Source #

Parse a ByteString to a JSON Value.

lookupKeyJson Source #

Arguments

:: Text

Key name

-> Value

JSON object

-> HttpT e r w s p m Value 

Object member lookup.

constructFromJson :: FromJSON a => Value -> HttpT e r w s p m a Source #

Decode a Value to some other type.

Types

type Url = String Source #

To make type signatures nicer

data JsonError Source #

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

Constructors

JsonError String

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.

Testing

checkHttpM Source #

Arguments

:: Monad eff 
=> S s

Initial state

-> R e w r

Environment

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

Effect evaluator

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

Condense to IO

-> (q -> Bool)

Result check

-> Http e r w s p t 
-> Property 

Turn an Http into a Property; for testing with QuickCheck.

checkHttpTM Source #

Arguments

:: (Monad (m eff), Monad eff) 
=> S s

Initial state

-> R e w r

Environment

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

Effect evaluator

-> (forall u. eff u -> m eff u)

Lift effects to the inner monad

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

Condense to IO

-> (q -> Bool)

Result check

-> HttpT e r w s p (m eff) t 
-> Property 

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