Support a basic API
Use Servant to create a REST API supporting the following routes: - GET /number - POST /other The server interacts with a SQLite database.
This commit is contained in:
parent
ec90748b82
commit
660b8d43e5
4 changed files with 50 additions and 0 deletions
1
.gitignore
vendored
Normal file
1
.gitignore
vendored
Normal file
|
@ -0,0 +1 @@
|
|||
data.db
|
|
@ -3,6 +3,11 @@ let
|
|||
in pkgs.mkShell {
|
||||
buildInputs = with pkgs; [
|
||||
(haskellPackages.ghcWithPackages (hpkgs: with hpkgs; [
|
||||
hpkgs.servant-server
|
||||
hpkgs.aeson
|
||||
hpkgs.resource-pool
|
||||
hpkgs.sqlite-simple
|
||||
hpkgs.warp
|
||||
]))
|
||||
];
|
||||
}
|
||||
|
|
39
src/API.hs
Normal file
39
src/API.hs
Normal file
|
@ -0,0 +1,39 @@
|
|||
{-# LANGUAGE DataKinds #-}
|
||||
{-# LANGUAGE TypeApplications #-}
|
||||
{-# LANGUAGE DeriveGeneric #-}
|
||||
{-# LANGUAGE TypeOperators #-}
|
||||
{-# LANGUAGE KindSignatures #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
--------------------------------------------------------------------------------
|
||||
module API where
|
||||
--------------------------------------------------------------------------------
|
||||
import qualified Data.Pool as DP
|
||||
import qualified Database.SQLite.Simple as DB
|
||||
|
||||
import Data.Aeson
|
||||
import GHC.Generics
|
||||
import GHC.TypeLits
|
||||
import Network.Wai.Handler.Warp
|
||||
import Servant
|
||||
import Control.Monad.IO.Class
|
||||
--------------------------------------------------------------------------------
|
||||
|
||||
handlers :: DP.Pool DB.Connection -> Server API
|
||||
handlers pool = do
|
||||
getHandler pool :<|> pure 0
|
||||
|
||||
getHandler :: DP.Pool DB.Connection -> Handler Int
|
||||
getHandler pool =
|
||||
DP.withResource pool $ \conn -> do
|
||||
result <- liftIO $ DB.query_ conn "select 2 + 2"
|
||||
case result of
|
||||
[DB.Only x] -> pure x
|
||||
_ -> pure (-1)
|
||||
|
||||
type API = "number" :> Get '[JSON] Int
|
||||
:<|> "other" :> Post '[JSON] Int
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
pool <- DP.createPool (DB.open "data.db") DB.close 1 0.5 1
|
||||
run 3000 (serve (Proxy @ API) (handlers pool))
|
5
src/Main.hs
Normal file
5
src/Main.hs
Normal file
|
@ -0,0 +1,5 @@
|
|||
module Main where
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
putStrLn "Working..."
|
Loading…
Reference in a new issue