Skip to content

Instantly share code, notes, and snippets.

@Decoherence
Last active January 17, 2020 13:07
Show Gist options
  • Star 4 You must be signed in to star a gist
  • Fork 1 You must be signed in to fork a gist
  • Save Decoherence/70ad2317ab7e1c2e7f30 to your computer and use it in GitHub Desktop.
Save Decoherence/70ad2317ab7e1c2e7f30 to your computer and use it in GitHub Desktop.
Haskell: Bookstore REST API with PostgreSQL backend using Servant
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
import Control.Applicative
import Control.Monad.IO.Class
import Data.Aeson
import Data.Proxy
import Data.Text (Text)
import Database.PostgreSQL.Simple
import Database.PostgreSQL.Simple.FromRow
import Database.PostgreSQL.Simple.ToField
import Database.PostgreSQL.Simple.ToRow
import GHC.Generics
import Network.Wai.Handler.Warp hiding (Connection)
import Servant
data Book = Book
{ title :: Text
, author :: Text
} deriving Generic
-- JSON instances
instance FromJSON Book
instance ToJSON Book
-- PostgreSQL instances
instance FromRow Book where
fromRow = Book <$> field <*> field
instance ToRow Book where
toRow book = [ toField (title book)
, toField (author book)]
-- we explicitly say we expect a request body, of type Book
type BookApi = "books" :> ReqBody Book :> Post Book -- POST /books
:<|> "books" :> Get [Book] -- GET /books
server :: Connection -> Server BookApi
server conn = postBook
:<|> getBooks
where
-- the aforementioned 'ReqBody' automatically makes this handler
-- receive a Book argument
postBook book = liftIO $ execute conn "insert into books values (?, ?)" book >> return book
getBooks = liftIO $ query_ conn "select * from books"
bookApi :: Proxy BookApi
bookApi = Proxy
main :: IO ()
main = do
conn <- connectPostgreSQL "host=localhost user=qubit dbname=bookstore"
run 8080 (serve bookApi $ server conn)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment