examples: add GS7

This commit is contained in:
Alp Mestanogullari 2015-05-06 19:01:32 +02:00
parent ec95cb0355
commit c892aae429
2 changed files with 35 additions and 0 deletions

View File

@ -0,0 +1,33 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
module GS7 where
import Control.Monad.Trans.Either
import Control.Monad.Trans.Reader
import Network.Wai
import Servant
type ReaderAPI = "a" :> Get '[JSON] Int
:<|> "b" :> Get '[JSON] String
readerAPI :: Proxy ReaderAPI
readerAPI = Proxy
readerServerT :: ServerT ReaderAPI (Reader String)
readerServerT = a :<|> b
where a :: Reader String Int
a = return 1797
b :: Reader String String
b = ask
readerServer :: Server ReaderAPI
readerServer = enter readerToEither readerServerT
where readerToEither :: Reader String :~> EitherT ServantErr IO
readerToEither = Nat $ \r -> return (runReader r "hi")
app :: Application
app = serve readerAPI readerServer

View File

@ -8,6 +8,7 @@ import qualified GS3
import qualified GS4
import qualified GS5
import qualified GS6
import qualified GS7
app :: String -> Maybe Application
app n = case n of
@ -17,6 +18,7 @@ app n = case n of
"4" -> Just GS4.app
"5" -> Just GS5.app
"6" -> Just GS6.app
"7" -> Just GS7.app
_ -> Nothing
main :: IO ()