| Copyright | 2018 Automattic Inc. | 
|---|---|
| License | BSD3 | 
| Maintainer | Nathan Bloomfield (nbloomf@gmail.com) | 
| Stability | experimental | 
| Portability | POSIX | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Control.Monad.Script.Http
Description
A basic type and monad transformer transformer for describing HTTP interactions.
Synopsis
- type HttpT e r w s p = HttpTT e r w s p IdentityT
 - data HttpTT e r w s p t eff a
 - execHttpTT :: (Monad eff, Monad (t eff), MonadTrans t) => S s -> R e w r -> (forall u. P p u -> eff u) -> HttpTT e r w s p t eff a -> t eff (Either (E e) a, S s, W e w)
 - liftHttpTT :: (Monad eff, Monad (t eff), MonadTrans t) => t eff a -> HttpTT e r w s p t eff a
 - throwError :: (Monad eff, Monad (t eff), MonadTrans t) => e -> HttpTT e r w s p t eff a
 - throwJsonError :: (Monad eff, Monad (t eff), MonadTrans t) => JsonError -> HttpTT e r w s p t eff a
 - throwHttpException :: (Monad eff, Monad (t eff), MonadTrans t) => HttpException -> HttpTT e r w s p t eff a
 - throwIOException :: (Monad eff, Monad (t eff), MonadTrans t) => IOException -> HttpTT e r w s p t eff a
 - catchError :: (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) -> HttpTT e r w s p t eff a
 - catchJsonError :: (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) -> HttpTT e r w s p t eff a
 - catchHttpException :: (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) -> HttpTT e r w s p t eff a
 - catchIOException :: (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) -> HttpTT e r w s p t eff a
 - 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
 - printError :: (e -> String) -> E e -> String
 - data E e
 - ask :: (Monad eff, Monad (t eff), MonadTrans t) => HttpTT e r w s p t eff (R e w r)
 - 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
 - reader :: (Monad eff, Monad (t eff), MonadTrans t) => (R e w r -> a) -> HttpTT e r w s p t eff a
 - data R e w r = R {
- _logOptions :: LogOptions e w
 - _logEntryPrinter :: LogOptions e w -> LogEntry e w -> Maybe String
 - _logHandle :: Handle
 - _logLock :: Maybe (MVar ())
 - _uid :: String
 - _httpErrorInject :: HttpException -> Maybe e
 - _env :: r
 
 - basicEnv :: (Show e, Show w) => r -> R e w r
 - trivialEnv :: r -> R e w r
 - data LogOptions e w = LogOptions {
- _logColor :: Bool
 - _logJson :: Bool
 - _logSilent :: Bool
 - _logMinSeverity :: LogSeverity
 - _logHeaders :: Bool
 - _printUserError :: Bool -> e -> String
 - _printUserLog :: Bool -> w -> String
 
 - basicLogOptions :: (Show e, Show w) => LogOptions e w
 - trivialLogOptions :: LogOptions e w
 - logEntries :: W e w -> [w]
 - data LogSeverity
 - 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
 - data W e w
 - printHttpLogs :: Handle -> Maybe (MVar ()) -> LogOptions e w -> (LogOptions e w -> LogEntry e w -> Maybe String) -> W e w -> IO ()
 - basicLogEntryPrinter :: LogOptions e w -> LogEntry e w -> Maybe String
 - gets :: (Monad eff, Monad (t eff), MonadTrans t) => (S s -> a) -> HttpTT e r w s p t eff a
 - modify :: (Monad eff, Monad (t eff), MonadTrans t) => (S s -> S s) -> HttpTT e r w s p t eff ()
 - data S s = S {
- _httpOptions :: Options
 - _httpSession :: Maybe Session
 - _userState :: s
 
 - basicState :: s -> S s
 - prompt :: (Monad eff, Monad (t eff), MonadTrans t) => P p a -> HttpTT e r w s p t eff a
 - data P p a where
- HPutStrLn :: Handle -> String -> P p (Either IOException ())
 - HPutStrLnBlocking :: MVar () -> Handle -> String -> P p (Either IOException ())
 - GetSystemTime :: P p UTCTime
 - ThreadDelay :: Int -> P p ()
 - HttpGet :: Options -> Maybe Session -> Url -> P p (Either HttpException HttpResponse)
 - HttpPost :: Options -> Maybe Session -> Url -> ByteString -> P p (Either HttpException HttpResponse)
 - HttpDelete :: Options -> Maybe Session -> Url -> P p (Either HttpException HttpResponse)
 - P :: p a -> P p a
 
 - evalIO :: (p a -> IO a) -> P p a -> IO a
 - evalMockIO :: (p a -> MockIO s a) -> P p a -> MockIO s a
 - comment :: (Monad eff, Monad (t eff), MonadTrans t) => String -> HttpTT e r w s p t eff ()
 - wait :: (Monad eff, Monad (t eff), MonadTrans t) => Int -> HttpTT e r w s p t eff ()
 - logDebug :: (Monad eff, Monad (t eff), MonadTrans t) => w -> HttpTT e r w s p t eff ()
 - logInfo :: (Monad eff, Monad (t eff), MonadTrans t) => w -> HttpTT e r w s p t eff ()
 - logNotice :: (Monad eff, Monad (t eff), MonadTrans t) => w -> HttpTT e r w s p t eff ()
 - logWarning :: (Monad eff, Monad (t eff), MonadTrans t) => w -> HttpTT e r w s p t eff ()
 - logError :: (Monad eff, Monad (t eff), MonadTrans t) => w -> HttpTT e r w s p t eff ()
 - logCritical :: (Monad eff, Monad (t eff), MonadTrans t) => w -> HttpTT e r w s p t eff ()
 - logAlert :: (Monad eff, Monad (t eff), MonadTrans t) => w -> HttpTT e r w s p t eff ()
 - logEmergency :: (Monad eff, Monad (t eff), MonadTrans t) => w -> HttpTT e r w s p t eff ()
 - hPutStrLn :: (Monad eff, Monad (t eff), MonadTrans t) => Handle -> String -> HttpTT e r w s p t eff ()
 - hPutStrLnBlocking :: (Monad eff, Monad (t eff), MonadTrans t) => MVar () -> Handle -> String -> HttpTT e r w s p t eff ()
 - httpGet :: (Monad eff, Monad (t eff), MonadTrans t) => Url -> HttpTT e r w s p t eff HttpResponse
 - httpSilentGet :: (Monad eff, Monad (t eff), MonadTrans t) => Url -> HttpTT e r w s p t eff HttpResponse
 - httpPost :: (Monad eff, Monad (t eff), MonadTrans t) => Url -> ByteString -> HttpTT e r w s p t eff HttpResponse
 - httpSilentPost :: (Monad eff, Monad (t eff), MonadTrans t) => Url -> ByteString -> HttpTT e r w s p t eff HttpResponse
 - httpDelete :: (Monad eff, Monad (t eff), MonadTrans t) => Url -> HttpTT e r w s p t eff HttpResponse
 - httpSilentDelete :: (Monad eff, Monad (t eff), MonadTrans t) => Url -> HttpTT e r w s p t eff HttpResponse
 - parseJson :: (Monad eff, Monad (t eff), MonadTrans t) => ByteString -> HttpTT e r w s p t eff Value
 - lookupKeyJson :: (Monad eff, Monad (t eff), MonadTrans t) => Text -> Value -> HttpTT e r w s p t eff Value
 - constructFromJson :: (Monad eff, Monad (t eff), MonadTrans t, FromJSON a) => Value -> HttpTT e r w s p t eff a
 - type Url = String
 - data JsonError
 - data HttpResponse = HttpResponse {}
 - checkHttpTT :: (Monad eff, Monad (t eff), MonadTrans t, Show q) => S s -> R e w r -> (forall u. P p u -> eff u) -> (t eff (Either (E e) a, S s, W e w) -> IO q) -> (q -> Bool) -> HttpTT e r w s p t eff a -> Property
 
HttpT
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
| (MonadTrans t, forall (m :: Type -> Type). Monad m => Monad (t m)) => MonadTrans (HttpTT e r w s p t) Source # | |
Defined in Control.Monad.Script.Http  | |
| (Monad eff, Monad (t eff), MonadTrans t) => Monad (HttpTT e r w s p t eff) Source # | |
Defined in Control.Monad.Script.Http  | |
| (Monad eff, Monad (t eff), MonadTrans t) => Functor (HttpTT e r w s p t eff) Source # | |
| (Monad eff, Monad (t eff), MonadTrans t) => Applicative (HttpTT e r w s p t eff) Source # | |
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 #  | |
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.
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.
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.
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.
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.
Error type.
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.
Generic session environment.
Constructors
| R | |
Fields 
  | |
Environment constructor
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  | 
Instances
| Eq LogSeverity Source # | |
Defined in Data.LogSeverity  | |
| Ord LogSeverity Source # | |
Defined in Data.LogSeverity Methods compare :: LogSeverity -> LogSeverity -> Ordering # (<) :: LogSeverity -> LogSeverity -> Bool # (<=) :: LogSeverity -> LogSeverity -> Bool # (>) :: LogSeverity -> LogSeverity -> Bool # (>=) :: LogSeverity -> LogSeverity -> Bool # max :: LogSeverity -> LogSeverity -> LogSeverity # min :: LogSeverity -> LogSeverity -> LogSeverity #  | |
| Show LogSeverity Source # | |
Defined in Data.LogSeverity Methods showsPrec :: Int -> LogSeverity -> ShowS # show :: LogSeverity -> String # showList :: [LogSeverity] -> ShowS #  | |
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.
Log type
printHttpLogs :: Handle -> Maybe (MVar ()) -> LogOptions e w -> (LogOptions e w -> LogEntry e w -> Maybe String) -> W e w -> IO () Source #
All log statements should go through logNow.
basicLogEntryPrinter :: LogOptions e w -> LogEntry e w -> Maybe String 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.
State type
Constructors
| S | |
Fields 
  | |
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.
Atomic effects
Constructors
| HPutStrLn :: Handle -> String -> P p (Either IOException ()) | |
| HPutStrLnBlocking :: MVar () -> Handle -> String -> P p (Either IOException ()) | |
| GetSystemTime :: P p UTCTime | |
| ThreadDelay :: Int -> P p () | |
| HttpGet :: Options -> Maybe Session -> Url -> P p (Either HttpException HttpResponse) | |
| HttpPost :: Options -> Maybe Session -> Url -> ByteString -> P p (Either HttpException HttpResponse) | |
| HttpDelete :: Options -> Maybe Session -> Url -> P p (Either HttpException HttpResponse) | |
| P :: p a -> P p 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) => String -> HttpTT e r w s p t eff () Source #
Write a comment to the log
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 -> String -> 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 -> String -> 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.
Arguments
| :: (Monad eff, Monad (t eff), MonadTrans t) | |
| => Url | |
| -> ByteString | Payload  | 
| -> HttpTT e r w s p t eff HttpResponse | 
Run a POST request
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.
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
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   | 
data HttpResponse Source #
Non-opaque HTTP response type.
Constructors
| HttpResponse | |
Instances
| Eq HttpResponse Source # | |
Defined in Network.HTTP.Client.Extras  | |
| Show HttpResponse Source # | |
Defined in Network.HTTP.Client.Extras Methods showsPrec :: Int -> HttpResponse -> ShowS # show :: HttpResponse -> String # showList :: [HttpResponse] -> ShowS #  | |
Testing
Arguments
| :: (Monad eff, Monad (t eff), MonadTrans t, Show q) | |
| => 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   | 
| -> (q -> Bool) | Result check  | 
| -> HttpTT e r w s p t eff a | |
| -> Property | 
Turn an HttpTT into a property; for testing with QuickCheck.