Appendix E. http-conduit

Most of Yesod is about serving content over HTTP. But that’s only half the story: someone has to receive it. And even when you’re writing a web app, sometimes that someone will be you. If you want to consume content from other services or interact with RESTful APIs, you’ll need to write client code. And the recommended approach for that is http-conduit.

This chapter is not directly connected to Yesod, and will be generally useful for anyone wanting to make HTTP requests.

Synopsis

{-# LANGUAGE OverloadedStrings #-}
import Network.HTTP.Conduit -- the main module

-- The streaming interface uses conduits
import Data.Conduit
import Data.Conduit.Binary (sinkFile)

import qualified Data.ByteString.Lazy as L
import Control.Monad.IO.Class (liftIO)

main :: IO ()
main = do
    -- Simplest query: just download the information from the given URL as a
    -- lazy ByteString.
    simpleHttp "http://www.example.com/foo.txt" >>= L.writeFile "foo.txt"

    -- Use the streaming interface instead. We need to run all of this inside a
    -- ResourceT, to ensure that all our connections get properly cleaned up in
    -- the case of an exception.
    runResourceT $ do
        -- We need a Manager, which keeps track of open connections. simpleHttp
        -- creates a new manager on each run (i.e., it never reuses
        -- connections).
        manager <- liftIO $ newManager def

        -- A more efficient version of the simpleHttp query above. First we
        -- parse the URL to a request.
        req <- liftIO $ parseUrl "http://www.example.com/foo.txt"

        -- Now ...

Get Developing Web Applications with Haskell and Yesod now with the O’Reilly learning platform.

O’Reilly members experience books, live events, courses curated by job role, and more from O’Reilly and nearly 200 top publishers.