examples: add GS4

This commit is contained in:
Alp Mestanogullari 2015-05-06 13:36:04 +02:00
parent f3002b36da
commit e81ac8fbc5
3 changed files with 67 additions and 0 deletions

View file

@ -0,0 +1,63 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
module GS4 where
import Data.Aeson
import Data.Foldable (foldMap)
import GHC.Generics
import Lucid
import Network.Wai
import Servant
import Servant.HTML.Lucid
data Person = Person
{ firstName :: String
, lastName :: String
, age :: Int
} deriving Generic -- for the JSON instance
-- JSON serialization
instance ToJSON Person
-- HTML serialization of a single person
instance ToHtml Person where
toHtml p =
tr_ $ do
td_ (toHtml $ firstName p)
td_ (toHtml $ lastName p)
td_ (toHtml . show $ age p)
toHtmlRaw = toHtml
-- HTML serialization of a list of persons
instance ToHtml [Person] where
toHtml persons = table_ $ do
tr_ $ do
td_ "first name"
td_ "last name"
td_ "age"
foldMap toHtml persons
toHtmlRaw = toHtml
persons :: [Person]
persons =
[ Person "Isaac" "Newton" 372
, Person "Albert" "Einstein" 136
]
type PersonAPI = "persons" :> Get '[JSON, HTML] [Person]
personAPI :: Proxy PersonAPI
personAPI = Proxy
server :: Server PersonAPI
server = return persons
app :: Application
app = serve personAPI server

View file

@ -5,12 +5,14 @@ import System.Environment
import qualified GS1
import qualified GS2
import qualified GS3
import qualified GS4
app :: String -> Maybe Application
app n = case n of
"1" -> Just GS1.app
"2" -> Just GS2.app
"3" -> Just GS3.app
"4" -> Just GS4.app
_ -> Nothing
main :: IO ()

View file

@ -20,7 +20,9 @@ executable getting-started
aeson >= 0.8
, base >= 4.7
, either
, lucid
, servant
, servant-lucid
, servant-server
, time
, wai