about summary refs log tree commit diff
diff options
context:
space:
mode:
-rw-r--r--.gitignore1
-rw-r--r--shell.nix5
-rw-r--r--src/API.hs39
-rw-r--r--src/Main.hs5
4 files changed, 50 insertions, 0 deletions
diff --git a/.gitignore b/.gitignore
new file mode 100644
index 000000000000..e604003590fc
--- /dev/null
+++ b/.gitignore
@@ -0,0 +1 @@
+data.db
\ No newline at end of file
diff --git a/shell.nix b/shell.nix
index 3a5a4ef9ecc5..96c18c8e9f90 100644
--- a/shell.nix
+++ b/shell.nix
@@ -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
     ]))
   ];
 }
diff --git a/src/API.hs b/src/API.hs
new file mode 100644
index 000000000000..b2c7fd57d67f
--- /dev/null
+++ b/src/API.hs
@@ -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))
diff --git a/src/Main.hs b/src/Main.hs
new file mode 100644
index 000000000000..7ec8d9f8ca82
--- /dev/null
+++ b/src/Main.hs
@@ -0,0 +1,5 @@
+module Main where
+
+main :: IO ()
+main = do
+  putStrLn "Working..."