jon/src/Jon/Main.hs

44 lines
1.1 KiB
Haskell

{-# LANGUAGE OverloadedStrings #-}
module Jon.Main
( main
, runFunction
, runQuery
, runIns
) where
import Control.Exception (bracket)
import Database.Beam
import Database.Beam.Postgres
import Servant (Proxy(..), serve)
import System.Environment
import Network.Wai.Handler.Warp (run)
import qualified Data.ByteString.Char8 as BS8
import Jon.Server (JonAPI, server)
main :: IO ()
main = withGarfieldConn (run 8080 . serve (Proxy :: Proxy JonAPI) . server)
withGarfieldConn = bracket
(do pass <- getEnv "JON_PASS"
connectPostgreSQL $ BS8.pack $ "host=localhost dbname=garfield password=" ++ pass)
close
runQuery
:: (FromBackendRow Postgres (QExprToIdentity e), Projectible Postgres e)
=> Q Postgres db QBaseScope e
-> IO [QExprToIdentity e]
runQuery q = withGarfieldConn $ \conn -> runBeamPostgresDebug putStrLn conn $ runSelectReturningList $ select q
runIns
:: SqlInsert Postgres table
-> IO ()
runIns i = withGarfieldConn $ \conn -> runBeamPostgresDebug putStrLn conn $ runInsert i
runFunction
:: (Connection -> IO a)
-> IO a
runFunction = withGarfieldConn