HELPS/src/Handlers.hs

43 lines
1.3 KiB
Haskell

module Handlers where
import Core
import Database
import Logger
import qualified Data.ByteString.Char8 as C
import Data.List
import qualified Data.Text as T
import Effectful
import Effectful.Error.Static (Error, throwError)
import Servant hiding ((:>), throwError)
import qualified Servant as S
type CRUD es = ( Database :> es, Logger :> es, Error ServerError :> es )
rootHandler :: (Logger :> es, Error ServerError :> es)
=> Eff es T.Text
rootHandler = (writeLog Info "Hit the root!") >>= \_ ->
return "Hello, World!"
userListHandler :: CRUD es
=> Eff es [User]
userListHandler = (writeLog Info "Selected all users!") >>= \_ ->
databaseRead_ "SELECT id, name FROM users"
userGetHandler :: CRUD es
=> UserId -> Eff es User
userGetHandler userId = databaseRead (queryUser userId) >>= \mUser ->
case mUser of
(a:_) -> pure a
[] -> pure (User (UserId 0) "No user found")
userPostHandler :: CRUD es
=> T.Text -> Eff es NoContent
userPostHandler name =
databaseWrite (writeUser name) >>= \_ -> return NoContent
userDeleteHandler :: CRUD es
=> UserId -> Eff es NoContent
userDeleteHandler userId =
databaseWrite (deleteUser userId) >>= \_ -> return NoContent