Skip to content

Instantly share code, notes, and snippets.

@deckool
Last active August 29, 2015 14:03
Show Gist options
  • Save deckool/f4e5686627ee52bc1fc3 to your computer and use it in GitHub Desktop.
Save deckool/f4e5686627ee52bc1fc3 to your computer and use it in GitHub Desktop.
http-streams
{-# LANGUAGE OverloadedStrings #-}
import System.IO.Streams (InputStream, OutputStream, stdout)
import qualified System.IO.Streams as Streams
import Network.Http.Client
import qualified Blaze.ByteString.Builder.Char8 as Builder
import Control.Applicative
import Control.Monad
import Data.Aeson (FromJSON, parseJSON, (.:))
import qualified Data.Aeson as AE
import Data.ByteString.Char8 (ByteString)
import qualified Data.ByteString.Lazy as LBS
import OpenSSL (withOpenSSL)
import qualified Text.DeadSimpleJSON as JSON
import Text.DeadSimpleJSON (JSON)
import qualified Data.ByteString.Char8 as B
data User = User
{ message :: String
, route1 :: String
} deriving Show
instance FromJSON User where
parseJSON (AE.Object v) = User <$>
v .: "message" <*>
v .: "route1"
parseJSON _ = mzero
test :: IO ()
test = do
q <- buildRequest $ do
http POST "/12289op1"
{- optional for 'encodedFormBody'
setContentType "application/x-www-form-urlencoded"
-}
setContentType "application/json" -- relevant for the current function
setHeader "User-Agent" "living room"
c <- establishConnection "http://requestb.in"
sendRequest c q (\o ->
Streams.write (Just (Builder.fromString "{\"movielist\": [\"Friday the 13th\", \"Caturday the 14th: The Final Chapter\", \"Sunday the 15th: A New Beginning\"]}")) o)
{- read docs on 'encodedFormBody'
let nvs = [("name","Kermit"),
("type","frog"),
("role","stagehand")]
sendRequest c q (encodedFormBody nvs)
-}
receiveResponse c (\p i -> do
putStrLn $ show $ getStatusCode p
putStrLn $ show $ getStatusMessage p
putStrLn $ show $ getHeader p "Sponsored-By" -- returns Just
case getHeader p "Sponsored-By" of -- using case for Just
Just x -> putStrLn $ show x
Nothing -> putStrLn $ show "Nothing"
xm <- Streams.read i
case xm of
Just x -> putStrLn $ show x
Nothing -> putStrLn $ show "ggg")
closeConnection c
sane = get "http://organicorange.ro:8000/" (\p i -> Streams.connect i stdout)
jsonHandler :: FromJSON a => Response -> InputStream ByteString -> IO (Maybe a)
jsonHandler r i = (AE.decode . LBS.fromChunks) <$> Streams.toList i
json :: IO ()
json = withOpenSSL $ do
user <- get "http://organicorange.ro:8000/" Main.jsonHandler :: IO (Maybe User)
case user of
Just u -> print $ route1 u
Nothing -> print "nu"
fson :: IO ()
fson = withOpenSSL $ do
user <- get "http://organicorange.ro:8000/" concatHandler
let x = read $ B.unpack user
print $ (x JSON.? "route1" :: String)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment