Reintroduce Debugging database handler; update main to allow for environment definition that will branch between all debug handlers or real effect handlers

This commit is contained in:
James Eversole 2024-11-05 15:18:21 -06:00
parent 13e8a11e83
commit 691e51660f
8 changed files with 137 additions and 48 deletions

1
.gitignore vendored
View File

@ -11,3 +11,4 @@ dist*
*.swp *.swp
.direnv* .direnv*
.envrc .envrc
*/result

View File

@ -17,7 +17,7 @@ How to navigate this codebase (as of revision 77131c4a):
- Effect definitions - Effect definitions
- Utility function for lifting IO to effectful's IOE - Utility function for lifting IO to effectful's IOE
- Database - Database
- Database effect handlers - Database effect handler
- Table definitons as functions - Table definitons as functions
- Helper functions for constructing SQL queries - Helper functions for constructing SQL queries
- Handlers - Handlers

View File

@ -25,7 +25,7 @@ type AppEff =
, Error ServerError , Error ServerError
] ]
data AppEnv = AppEnv { pool :: Pool Connection } data AppEnv = AppEnv { pool :: Maybe (Pool Connection) }
newtype UserId = UserId Int newtype UserId = UserId Int
deriving (Show, Generic, FromField, ToField, FromHttpApiData, ToHttpApiData) deriving (Show, Generic, FromField, ToField, FromHttpApiData, ToHttpApiData)

View File

@ -3,20 +3,21 @@ module Database where
import Core import Core
import Utility import Utility
import Control.Exception (IOException) import Control.Exception (IOException)
import Data.Aeson (ToJSON) import Data.Aeson (ToJSON)
import Data.ByteString (ByteString) import Data.ByteString (ByteString)
import Data.Maybe (listToMaybe) import Data.Maybe (listToMaybe)
import Data.Pool import Data.Pool
import qualified Data.Text as T import qualified Data.Text as T
import Data.Time (getCurrentTime, UTCTime)
import Database.PostgreSQL.Simple import Database.PostgreSQL.Simple
import Database.PostgreSQL.Simple.ToField (ToField) import Database.PostgreSQL.Simple.ToField (ToField)
import Effectful import Effectful
import Effectful.Dispatch.Dynamic import Effectful.Dispatch.Dynamic
import Effectful.Error.Static (Error) import Effectful.Error.Static (Error)
import Effectful.Reader.Static import Effectful.Reader.Static
import Effectful.State.Static.Local (State, get, put, evalState) import Effectful.State.Static.Local (State, get, put, evalState)
import Servant hiding ((:>), throwError) import Servant hiding ((:>), throwError)
type instance DispatchOf Database = 'Dynamic type instance DispatchOf Database = 'Dynamic
@ -45,32 +46,73 @@ runDatabaseIO :: DatabaseExeEffects es
=> Eff (Database : es) a -> Eff es a => Eff (Database : es) a -> Eff es a
runDatabaseIO = interpret $ \_ -> \case runDatabaseIO = interpret $ \_ -> \case
DatabaseInit -> do DatabaseInit -> do
AppEnv { pool } <- ask env <- ask
liftWithPool pool $ \conn -> do case pool env of
execute_ conn createUsersTable Just pool -> liftWithPool pool $ \conn -> do
execute_ conn createLogsTable execute_ conn createUsersTable
pure () execute_ conn createLogsTable
pure ()
Nothing -> do
databaseEscapeLog Error
"No database pool in scope; did you mean to run the mock handler?"
throwDefaultISE
DatabaseRead (statement, values) -> do DatabaseRead (statement, values) -> do
AppEnv { pool } <- ask env <- ask
liftWithPool pool $ \conn -> case pool env of
query conn statement (Only values) Just pool ->
liftWithPool pool $ \conn -> query conn statement (Only values)
Nothing -> do
databaseEscapeLog Error
"No database pool in scope; did you mean to run the mock handler?"
throwDefaultISE
DatabaseRead_ statement -> do DatabaseRead_ statement -> do
AppEnv { pool } <- ask env <- ask
liftWithPool pool $ \conn -> case pool env of
query_ conn statement Just pool -> liftWithPool pool $ \conn -> query_ conn statement
Nothing -> do
databaseEscapeLog Error
"No database pool in scope; did you mean to run the mock handler?"
throwDefaultISE
DatabaseWrite (statement, values) -> do DatabaseWrite (statement, values) -> do
AppEnv { pool } <- ask env <- ask
liftWithPool pool $ \conn -> do case pool env of
execute conn statement values Just pool -> liftWithPool pool $ \conn -> do
pure () execute conn statement values
pure ()
Nothing -> do
databaseEscapeLog Error
"No database pool in scope; did you mean to run the mock handler?"
throwDefaultISE
where where
liftWithPool :: (IOE :> es, Error ServerError :> es) liftWithPool :: (IOE :> es, Error ServerError :> es)
=> (Pool Connection) -> (Connection -> IO a) -> Eff es a => (Pool Connection) -> (Connection -> IO a) -> Eff es a
liftWithPool p f = liftIOE $ withResource p f liftWithPool p f = liftIOE $ withResource p f
runDatabaseDebug :: DatabaseExeEffects es
=> Eff (Database : es) a -> Eff es a
runDatabaseDebug = interpret $ \_ -> \case
DatabaseInit -> do
liftIOE $ putStrLn "Mocked setup of the database"
DatabaseRead (statement, values) -> do
liftIOE $ putStrLn
$ "Mocked a READ database operation with statement:\n"
++ show statement
++ "\nValues:\n"
++ show values
pure []
DatabaseRead_ statement -> do
liftIOE $ putStrLn "Mocked a READ database operation on all users"
pure []
DatabaseWrite (statement, values) -> do
liftIOE $ putStrLn
$ "Mocked a WRITE database operation with statement:\n"
++ show statement
++ "\nValues:\n"
++ show values
createConnectionPool :: ByteString -> IO (Pool Connection) createConnectionPool :: ByteString -> IO (Pool Connection)
createConnectionPool connectString = newPool $ defaultPoolConfig createConnectionPool connectString = newPool $ defaultPoolConfig
(connectPostgreSQL connectString) (connectPostgreSQL connectString)
@ -102,3 +144,11 @@ createLogsTable = "CREATE TABLE IF NOT EXISTS logs ( \
\ source VARCHAR(100), \ \ source VARCHAR(100), \
\ context JSONB \ \ context JSONB \
\);" \);"
databaseEscapeLog :: (IOE :> es, Error ServerError :> es) => LogLevel -> String -> Eff es ()
databaseEscapeLog level msg = do
time <- liftIOE getCurrentTime
liftIOE $ putStrLn
$ "TIMESTAMP: " ++ show time ++ "\n"
++ "LEVEL: " ++ show level ++ "\n"
++ "MESSAGE: " ++ msg

View File

@ -27,8 +27,8 @@ rootHandler = (writeLog Info "Hit the root!")
userListHandler :: CRUD es userListHandler :: CRUD es
=> Eff es (Html ()) => Eff es (Html ())
userListHandler = do userListHandler = do
writeLog Info "Selected all users!"
users <- databaseRead_ "SELECT id, name FROM users" users <- databaseRead_ "SELECT id, name FROM users"
writeLog Info "Selected all users!"
return $ V.baseDoc $ case users of return $ V.baseDoc $ case users of
[] -> warning "No users found" [] -> warning "No users found"
_ -> foldMap userHtml users _ -> foldMap userHtml users

View File

@ -9,8 +9,8 @@ import Effectful
import Effectful.Dispatch.Dynamic import Effectful.Dispatch.Dynamic
import Effectful.Error.Static (Error, throwError) import Effectful.Error.Static (Error, throwError)
import Effectful.Reader.Static import Effectful.Reader.Static
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Servant hiding ((:>)) import Servant hiding ((:>))
type LogToDatabase es = (Database :> es, Error ServerError :> es, IOE :> es) type LogToDatabase es = (Database :> es, Error ServerError :> es, IOE :> es)
@ -24,7 +24,7 @@ runLoggerConsole :: (Error ServerError :> es, IOE :> es)
=> Eff (Logger : es) a -> Eff es a => Eff (Logger : es) a -> Eff es a
runLoggerConsole = interpret $ \_ -> \case runLoggerConsole = interpret $ \_ -> \case
WriteLog level msg -> do WriteLog level msg -> do
time <- liftIOE getCurrentTime time <- liftIOE getCurrentTime
liftIOE $ putStrLn liftIOE $ putStrLn
$ "TIMESTAMP: " ++ show time ++ "\n" $ "TIMESTAMP: " ++ show time ++ "\n"
++ "LEVEL: " ++ show level ++ "\n" ++ "LEVEL: " ++ show level ++ "\n"

View File

@ -15,19 +15,48 @@ import Network.Wai.Handler.Warp (run)
import Network.Wai.Middleware.Static ((>->), staticPolicy, noDots, addBase) import Network.Wai.Middleware.Static ((>->), staticPolicy, noDots, addBase)
import Servant hiding ((:>), throwError, inject) import Servant hiding ((:>), throwError, inject)
import qualified Servant as S import qualified Servant as S
import System.Environment (lookupEnv)
--
-- Types
--
data RunMode = Production | Debug
proxy :: Proxy AppAPI
proxy = Proxy
-- --
-- Application -- Application
-- --
main :: IO () main :: IO ()
main = do main = do
pool <- createConnectionPool "host=localhost dbname=demo" (envPort, envMode) <- do
let env = AppEnv { pool = pool } port <- lookupEnv "PORT"
runAppEff env $ databaseInit env <- lookupEnv "ENVIRONMENT"
run port . middleware . serve proxy $ app env pure (port, env)
app :: AppEnv -> Server AppAPI let port = maybe 8080 read envPort
app env = hoistServer proxy (Handler . ExceptT . runAppEff env) handlers mode = case envMode of
Just "production" -> Production
_ -> Debug
env <- case mode of
Production -> do
dbPool <- createConnectionPool "host=localhost dbname=demo"
let env = AppEnv { pool = Just dbPool }
appEff env databaseInit
pure env
Debug -> do
let env = AppEnv { pool = Nothing }
appDebug env databaseInit
pure env
run port . middleware . serve proxy $ app env mode
app :: AppEnv -> RunMode -> Server AppAPI
app env Production = hoistServer proxy (Handler . ExceptT . appEff env) handlers
app env Debug = hoistServer proxy (Handler . ExceptT . appDebug env) handlers
handlers :: ServerT AppAPI AppEff handlers :: ServerT AppAPI AppEff
handlers = rootHandler handlers = rootHandler
@ -39,16 +68,22 @@ handlers = rootHandler
middleware :: Application -> Application middleware :: Application -> Application
middleware = staticPolicy (noDots >-> addBase "data/assets/public") middleware = staticPolicy (noDots >-> addBase "data/assets/public")
runAppEff :: AppEnv -> AppEff a -> IO (Either ServerError a) --
runAppEff env = runEff -- Effect Stacks
--
appEff :: AppEnv -> AppEff a -> IO (Either ServerError a)
appEff env = runEff
. runErrorNoCallStack . runErrorNoCallStack
. runReader env . runReader env
. runDatabaseIO . runDatabaseIO
. runLoggerPSQL . runLoggerPSQL
. inject . inject
port :: Int appDebug :: AppEnv -> AppEff a -> IO (Either ServerError a)
port = 8080 appDebug env = runEff
. runErrorNoCallStack
proxy :: Proxy AppAPI . runReader env
proxy = Proxy . runDatabaseDebug
. runLoggerConsole
. inject

View File

@ -20,9 +20,12 @@ liftIOE m = liftIO m `catch` \(e::IOException) -> do
-- Log IOExceptions to stdout -- Log IOExceptions to stdout
liftIO $ putStrLn $ "ERROR Exception: " ++ show e liftIO $ putStrLn $ "ERROR Exception: " ++ show e
-- Throw a custom Servant ServerError -- Throw a custom Servant ServerError
throwError $ ServerError throwDefaultISE
{ errHTTPCode = 500
, errReasonPhrase = "Internal Server Error" throwDefaultISE :: (IOE :> es, Error ServerError :> es) => Eff es a
, errBody = renderBS V.internalServerError throwDefaultISE = throwError $ ServerError
, errHeaders = [] { errHTTPCode = 500
} , errReasonPhrase = "Internal Server Error"
, errBody = renderBS V.internalServerError
, errHeaders = []
}