Skip to content

Instantly share code, notes, and snippets.

@domenkozar
Created April 19, 2018 23:08
Show Gist options
  • Save domenkozar/f08b27d75a3017e5bfd607f25854db30 to your computer and use it in GitHub Desktop.
Save domenkozar/f08b27d75a3017e5bfd607f25854db30 to your computer and use it in GitHub Desktop.
#!/usr/bin/env nix-shell
#!nix-shell -i runghc -p "haskellPackages.ghcWithPackages (pkgs: with pkgs; [servant-generic servant-client])"
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE OverloadedStrings #-}
import Data.Aeson.Types
import Data.Text
import Data.Time (UTCTime)
import Data.Time.Calendar
import GHC.Generics
import Servant.API
import Servant
import Servant.Client
import Servant.Generic
import Network.HTTP.Client (newManager, defaultManagerSettings)
data Site route = Site
{ about :: route :-
Capture "x" Text :> Get '[JSON] Text
, faq :: route :-
Capture "x" Int :> Get '[JSON] Int
} deriving Generic
type UserAPI = ToServant (Site AsApi)
userAPI :: Proxy UserAPI
userAPI = Proxy
data AsClient
type instance AsClient :- api = Client ClientM api
myClient :: Site AsClient
myClient = Site
{ about = fromServant :: Text -> ClientM Text
, faq = fromServant :: Int -> ClientM Int
}
-- xxx = client userAPI
main :: IO ()
main = do
manager <- newManager defaultManagerSettings
let env = mkClientEnv manager $ BaseUrl Http "localhost" 8090 ""
res <- runClientM (about myClient 3) env
case res of
Left err -> putStrLn $ "Error: " ++ show err
Right books -> print books
-- https://github.com/chpatrick/servant-generic/pull/2/files
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment