I'm building a Haskell Servant
API using an SQL library called Squeal
:
https://github.com/morphismtech/squeal
I need help getting the types correct so the app compiles.
My Schema is of type
type Schema = '["users" ::: UsersTable, ...]
type Schemas = Public Schema
Where Public
is a type family for a single schema database. It's from:
http://hackage.haskell.org/package/squeal-postgresql-0.5.1.0/docs/Squeal-PostgreSQL-Schema.html
I'm trying to pass the Connection Pool in a Reader like this:
import qualified Squeal.PostgreSQL as S
import qualified Squeal.PostgreSQL.Pool as SPG
newtype AppT m a
= AppT
{ runApp :: ReaderT SquealPool (ExceptT ServerError m) a
} deriving
( Functor, Applicative, Monad, MonadReader SquealPool, MonadError ServerError
, MonadIO
)
type App = AppT IO
type SquealPool = SPG.Pool (SQ.K S.Connection Schema)
My SQL query & session are something like this:
emailQuery :: Query_ Schemas (Only Text) UserEmail
emailQuery = select (#email `as` #email)
(from (table #users) & where_ (#email .== param @1))
emailTakenSession
:: (MonadReader SquealPool m, MonadPQ Schemas m, MonadIO m)
=> Text
-> m UserEmail
emailTakenSession email = do
result <- runQueryParams emailQuery (Only email)
email <- getRow 1 result
return email
Finally, I'm using them in the Servant
handlers like this:
emailTaken :: MonadIO m => Text -> AppT m APIEmail
emailTaken emailStr = do
pool <- ask -- this produces error
result <- liftIO $ runPoolPQ (Q.emailTakenSession emailStr) pool
return $ APIEmail result True
The compiler reports an error in ask
in emailTaken
:
* Couldn't match kind `[(ghc-prim-0.5.3:GHC.Types.Symbol,
Squeal.PostgreSQL.Schema.SchemumType)]'
with `Squeal.PostgreSQL.Schema.SchemumType'
From what I understand, it's trying to match type family Schemas
with type Schema
.
How do I need to edit the type signatures to get this to compile and work?
Particularly emailTakenSession
is probably off at least.
In the interest of completeness for other readers, I needed to change
type SquealPool = SPG.Pool (SQ.K S.Connection Schema)
into
type SquealPool = SPG.Pool (S.K S.Connection '["public" ::: Schema])
The type family would resolve to this anyway, and this way I'm not providing an illegal construct (a type family) to MonadReader derivation in AppT
.
Here's a skeleton of how I combine Squeal & Servant.
{-# LANGUAGE
DataKinds
, OverloadedLabels
, OverloadedStrings
, PolyKinds
#-}
module SquealServant where
import Control.Monad.IO.Class
import Data.String
import Servant
import Squeal.PostgreSQL
import Data.Pool
type DB = Public Schema
type Schema = '[] -- your schema here
type API = Get '[JSON] String -- your api here
type PoolDB = Pool (K Connection DB)
application :: PoolDB -> Application
application pool = serve api (server pool)
server :: PoolDB -> Server API
server pool = hoistServer api (handler pool) serverT
handler :: PoolDB -> PQ DB DB IO x -> Handler x
handler pool session = do
errOrResult <- liftIO . usingConnectionPool pool $
trySqueal (transactionally_ session)
case errOrResult of
Left err -> throwError (sqlErr err)
Right result -> return result
sqlErr :: SquealException -> ServerError
sqlErr err = err500 { errBody = fromString (show err) }
api :: Proxy API
api = Proxy
serverT :: ServerT API (PQ DB DB IO)
serverT = hello
hello :: PQ DB DB IO String
hello = do
Only greeting <- getRow 0 =<< runQuery helloQ
return greeting
helloQ :: Query_ DB () (Only String)
helloQ = values_ ("hello world" `as` #fromOnly)
usingConnectionPool :: PoolDB -> PQ DB DB IO x -> IO x
usingConnectionPool pool (PQ session) = unK <$> withResource pool session