Copyright | 2018 Automattic Inc. |
---|---|
License | BSD3 |
Maintainer | Nathan Bloomfield (nbloomf@gmail.com) |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
A basic type and monad for describing HTTP interactions.
Synopsis
- type Http e r w s p a = HttpT e r w s p Identity a
- execHttpM :: Monad eff => S s -> R e w r -> (forall u. P p u -> eff u) -> Http e r w s p t -> eff (Either (E e) t, S s, W e w)
- data HttpT e r w s p m a
- execHttpTM :: (Monad (m eff), Monad eff) => S s -> R e w r -> (forall u. P p u -> eff u) -> (forall u. eff u -> m eff u) -> HttpT e r w s p (m eff) t -> m eff (Either (E e) t, S s, W e w)
- liftHttpT :: Monad m => m a -> HttpT e r w s p m a
- throwError :: e -> HttpT e r w s p m a
- throwJsonError :: JsonError -> HttpT e r w s p m a
- throwHttpException :: HttpException -> HttpT e r w s p m a
- throwIOException :: IOException -> HttpT e r w s p m a
- catchError :: HttpT e r w s p m a -> (e -> HttpT e r w s p m a) -> HttpT e r w s p m a
- catchJsonError :: HttpT e r w s p m a -> (JsonError -> HttpT e r w s p m a) -> HttpT e r w s p m a
- catchHttpException :: HttpT e r w s p m a -> (HttpException -> HttpT e r w s p m a) -> HttpT e r w s p m a
- catchIOException :: HttpT e r w s p m a -> (IOException -> HttpT e r w s p m a) -> HttpT e r w s p m a
- catchAnyError :: HttpT e r w s p m a -> (e -> HttpT e r w s p m a) -> (HttpException -> HttpT e r w s p m a) -> (IOException -> HttpT e r w s p m a) -> (JsonError -> HttpT e r w s p m a) -> HttpT e r w s p m a
- printError :: (e -> String) -> E e -> String
- data E e
- ask :: HttpT e r w s p m (R e w r)
- 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
- reader :: (R e w r -> a) -> HttpT e r w s p m 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 :: LogSeverity -> HttpT e r w s p m a -> HttpT e r w s p m 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 :: (S s -> a) -> HttpT e r w s p m a
- modify :: (S s -> S s) -> HttpT e r w s p m ()
- data S s = S {
- _httpOptions :: Options
- _httpSession :: Maybe Session
- _userState :: s
- basicState :: s -> S s
- prompt :: P p a -> HttpT e r w s p m 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 :: String -> HttpT e r w s p m ()
- wait :: Int -> HttpT e r w s p m ()
- logDebug :: w -> HttpT e r w s p m ()
- logInfo :: w -> HttpT e r w s p m ()
- logNotice :: w -> HttpT e r w s p m ()
- logWarning :: w -> HttpT e r w s p m ()
- logError :: w -> HttpT e r w s p m ()
- logCritical :: w -> HttpT e r w s p m ()
- logAlert :: w -> HttpT e r w s p m ()
- logEmergency :: w -> HttpT e r w s p m ()
- hPutStrLn :: Handle -> String -> HttpT e r w s p m ()
- hPutStrLnBlocking :: MVar () -> Handle -> String -> HttpT e r w s p m ()
- httpGet :: Url -> HttpT e r w s p m HttpResponse
- httpSilentGet :: Url -> HttpT e r w s p m HttpResponse
- httpPost :: Url -> ByteString -> HttpT e r w s p m HttpResponse
- httpSilentPost :: Url -> ByteString -> HttpT e r w s p m HttpResponse
- httpDelete :: Url -> HttpT e r w s p m HttpResponse
- httpSilentDelete :: Url -> HttpT e r w s p m HttpResponse
- parseJson :: ByteString -> HttpT e r w s p m Value
- lookupKeyJson :: Text -> Value -> HttpT e r w s p m Value
- constructFromJson :: FromJSON a => Value -> HttpT e r w s p m a
- type Url = String
- data JsonError
- data HttpResponse = HttpResponse {}
- checkHttpM :: Monad eff => S s -> R e w r -> (forall u. P p u -> eff u) -> (eff (Either (E e) t, S s, W e w) -> IO q) -> (q -> Bool) -> Http e r w s p t -> Property
- checkHttpTM :: (Monad (m eff), Monad eff) => S s -> R e w r -> (forall u. P p u -> eff u) -> (forall u. eff u -> m eff u) -> (m eff (Either (E e) t, S s, W e w) -> IO q) -> (q -> Bool) -> HttpT e r w s p (m eff) t -> Property
Http
:: 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 # | |
Functor (HttpT e r w s p m) Source # | |
Applicative (HttpT e r w s p m) Source # | |
Defined in Control.Monad.Script.Http 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 # |
:: (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.
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.
Re-throws other error types.
Re-throws other error types.
:: 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.
:: 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.
catchAnyError :: HttpT e r w s p m a -> (e -> HttpT e r w s p m a) -> (HttpException -> HttpT e r w s p m a) -> (IOException -> HttpT e r w s p m a) -> (JsonError -> HttpT e r w s p m a) -> HttpT e r w s p m a Source #
Handle any thrown error. To handle only errors of a specific type, see catchError
, catchJsonError
, catchIOException
, or catchHttpException
.
Reader
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.
Generic session environment.
R | |
|
Environment constructor
data LogOptions e w Source #
Options for tweaking the logs.
LogOptions | |
|
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.
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 (==) :: LogSeverity -> LogSeverity -> Bool # (/=) :: LogSeverity -> LogSeverity -> Bool # | |
Ord LogSeverity Source # | |
Defined in Data.LogSeverity 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 showsPrec :: Int -> LogSeverity -> ShowS # show :: LogSeverity -> String # showList :: [LogSeverity] -> ShowS # |
setLogSeverity :: LogSeverity -> HttpT e r w s p m a -> HttpT e r w s p m 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 LogEntry
s.
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.
basicState :: s -> S s Source #
State constructor
Prompt
Atomic effects
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 |
API
logWarning :: w -> HttpT e r w s p m () Source #
For warning conditions
logCritical :: w -> HttpT e r w s p m () Source #
For critical conditions
logEmergency :: w -> HttpT e r w s p m () Source #
System is unusable
IO
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
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.
:: 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
.
Object member lookup.
constructFromJson :: FromJSON a => Value -> HttpT e r w s p m a Source #
Decode a Value
to some other type.
Types
Represents the kinds of errors that can occur when parsing and decoding JSON.
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.
Instances
Eq HttpResponse Source # | |
Defined in Network.HTTP.Client.Extras (==) :: HttpResponse -> HttpResponse -> Bool # (/=) :: HttpResponse -> HttpResponse -> Bool # | |
Show HttpResponse Source # | |
Defined in Network.HTTP.Client.Extras showsPrec :: Int -> HttpResponse -> ShowS # show :: HttpResponse -> String # showList :: [HttpResponse] -> ShowS # |
Testing
:: (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 |
-> (q -> Bool) | Result check |
-> HttpT e r w s p (m eff) t | |
-> Property |
Turn an HttpT
into a property; for testing with QuickCheck.