Skip to content

Instantly share code, notes, and snippets.

@michaelt
Last active March 22, 2024 09:37
Show Gist options
  • Star 4 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save michaelt/2dcea1ba32562c091357 to your computer and use it in GitHub Desktop.
Save michaelt/2dcea1ba32562c091357 to your computer and use it in GitHub Desktop.
A trivial get request which yields a 'byte stream' for manipulation. Here we number the verses of a bible from Project Gutenberg...
{-#LANGUAGE OverloadedStrings #-}
import Streaming
import Streaming.Prelude (each, next, yield)
import qualified Data.ByteString.Streaming.Char8 as Q
import qualified Data.ByteString.Char8 as B
import qualified Streaming.Prelude as S
import qualified Control.Foldl as L
import Data.ByteString.Streaming.HTTP -- git clone https://github.com/michaelt/streaming-http
-- cabal install ./streaming-http
infixl 5 >>>; (>>>) = flip (.)
infixl 1 &; (&) = flip ($)
main = do
req <- parseUrl "https://raw.githubusercontent.com/michaelt/kjv/master/kjv.txt"
m <- newManager tlsManagerSettings
withHTTP req m $ \resp ->
resp & -- Response (Q.ByteString IO ())
responseBody -- Q.ByteString IO ()
>>> Q.lines -- Stream (Q.ByteString IO) IO ()
>>> Q.denull -- Stream (Q.ByteString IO) IO ()
>>> interleaves numerals -- Stream (Q.ByteString IO) IO ()
>>> Q.unlines -- Q.ByteString IO ()
>>> Q.stdout -- IO ()
where
numerals = maps padded (S.enumFrom 1)
padded (n:>r) = Q.chunk stuff >> return r
where
len = length (show n); diff = 5 - len
padding = if diff > 0 then B.replicate diff ' ' else ""
stuff = padding `mappend` B.pack (show n ++ " ")
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment