Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module replicates `pipes-http` as closely as will type-check, adding a
conduit-like http
in ResourceT
and a primitive simpleHTTP
that emits
a streaming bytestring rather than a lazy one.
Here is an example GET request that streams the response body to standard output:
import qualified Data.ByteString.Streaming as Q import Data.ByteString.Streaming.HTTP main = do req <- parseRequest "https://www.example.com" m <- newManager tlsManagerSettings withHTTP req m $ \resp -> Q.stdout (responseBody resp)
Here is an example POST request that also streams the request body from standard input:
{-#LANGUAGE OverloadedStrings #-} import qualified Data.ByteString.Streaming as Q import Data.ByteString.Streaming.HTTP main = do req <- parseRequest "https://httpbin.org/post" let req' = req { method = "POST" , requestBody = stream Q.stdin } m <- newManager tlsManagerSettings withHTTP req' m $ \resp -> Q.stdout (responseBody resp)
Here is the GET request modified to use http
and write to a file. runResourceT
manages the file handle and the interaction.
import qualified Data.ByteString.Streaming as Q import Data.ByteString.Streaming.HTTP main = do req <- parseUrlThrow "https://www.example.com" m <- newManager tlsManagerSettings runResourceT $ do resp <- http request manager Q.writeFile "example.html" (responseBody resp)
simpleHTTP
can be used in ghci
like so:
ghci> runResourceT $ Q.stdout $ Q.take 137 $ simpleHTTP "http://lpaste.net/raw/13" -- Adaptation and extension of a parser for data definitions given in -- appendix of G. Huttons's paper - Monadic Parser Combinators. --
Synopsis
- withHTTP :: Request -> Manager -> (Response (ByteString IO ()) -> IO a) -> IO a
- http :: MonadResource m => Request -> Manager -> m (Response (ByteString m ()))
- streamN :: Int64 -> ByteString IO () -> RequestBody
- stream :: ByteString IO () -> RequestBody
- simpleHTTP :: MonadResource m => String -> ByteString m ()
- module Network.HTTP.Client
- module Network.HTTP.Client.TLS
- data ResourceT (m :: Type -> Type) a
- class MonadIO m => MonadResource (m :: Type -> Type) where
- liftResourceT :: ResourceT IO a -> m a
- runResourceT :: MonadUnliftIO m => ResourceT m a -> m a
Streaming Interface
http :: MonadResource m => Request -> Manager -> m (Response (ByteString m ())) Source #
streamN :: Int64 -> ByteString IO () -> RequestBody Source #
Create a RequestBody
from a content length and an effectful ByteString
stream :: ByteString IO () -> RequestBody Source #
Create a RequestBody
from an effectful ByteString
stream
is more flexible than streamN
, but requires the server to support
chunked transfer encoding.
ghci testing
simpleHTTP :: MonadResource m => String -> ByteString m () Source #
This is a quick method - oleg would call it 'unprofessional' - to bring a web page in view. It sparks its own internal manager and closes itself. Thus something like this makes sense
>>>
runResourceT $ Q.putStrLn $ simpleHttp "http://lpaste.net/raw/12"
chunk _ [] = [] chunk n xs = let h = take n xs in h : (chunk n (drop n xs))
but if you try something like
>>>
rest <- runResourceT $ Q.putStrLn $ Q.splitAt 40 $ simpleHTTP "http://lpaste.net/raw/146532"
import Data.ByteString.Streaming.HTTP
it will just be good luck if with
>>>
runResourceT $ Q.putStrLn rest
you get the rest of the file:
import qualified Data.ByteString.Streaming.Char8 as Q main = runResourceT $ Q.putStrLn $ simpleHTTP "http://lpaste.net/raw/146532"
rather than
*** Exception: <socket: 13>: hGetBuf: illegal operation (handle is closed)
Since, of course, the handle was already closed by the first use of runResourceT
.
The same applies of course to the more hygienic withHTTP
above,
which permits one to extract an IO (ByteString IO r)
, by using splitAt
or
the like.
The reaction of some streaming-io libraries was simply to forbid
operations like splitAt
. That this paternalism was not viewed
as simply outrageous is a consequence of the opacity of the
older iteratee-io libraries. It is obvious that I can no more run an
effectful bytestring after I have made its effects impossible by
using runResourceT
(which basically means closeEverythingDown
).
I might as well try to run it after tossing my machine into the flames.
Similarly, it is obvious that I cannot read from a handle after I have
applied hClose
; there is simply no difference between the two cases.
re-exports
module Network.HTTP.Client
module Network.HTTP.Client.TLS
data ResourceT (m :: Type -> Type) a #
The Resource transformer. This transformer keeps track of all registered
actions, and calls them upon exit (via runResourceT
). Actions may be
registered via register
, or resources may be allocated atomically via
allocate
. allocate
corresponds closely to bracket
.
Releasing may be performed before exit via the release
function. This is a
highly recommended optimization, as it will ensure that scarce resources are
freed early. Note that calling release
will deregister the action, so that
a release action will only ever be called once.
Since 0.3.0
Instances
class MonadIO m => MonadResource (m :: Type -> Type) where #
A Monad
which allows for safe resource allocation. In theory, any monad
transformer stack which includes a ResourceT
can be an instance of
MonadResource
.
Note: runResourceT
has a requirement for a MonadUnliftIO m
monad,
which allows control operations to be lifted. A MonadResource
does not
have this requirement. This means that transformers such as ContT
can be
an instance of MonadResource
. However, the ContT
wrapper will need to be
unwrapped before calling runResourceT
.
Since 0.3.0
liftResourceT :: ResourceT IO a -> m a #
Lift a ResourceT IO
action into the current Monad
.
Since 0.4.0
Instances
runResourceT :: MonadUnliftIO m => ResourceT m a -> m a #
Unwrap a ResourceT
transformer, and call all registered release actions.
Note that there is some reference counting involved due to resourceForkIO
.
If multiple threads are sharing the same collection of resources, only the
last call to runResourceT
will deallocate the resources.
NOTE Since version 1.2.0, this function will throw a
ResourceCleanupException
if any of the cleanup functions throw an
exception.
Since: resourcet-0.3.0