mu-persistent-0.3.1.0: Utilities for interoperation between Mu and Persistent
Safe HaskellNone
LanguageHaskell2010

Mu.Adapter.Persistent

Description

The persistent library, and in particular its quasi-quoters for entities, generate data types which do not look exactly as plain records. This module defines some wrappers which modify the ToSchema and FromSchema derivation to work with them.

Synopsis

Wrappers for use with DerivingVia

newtype WithEntityNestedId (ty :: Symbol) (fmap :: Mappings Symbol Symbol) a Source #

Wrapper for Entity to be used with DerivingVia. This wrappers indicates that the identifier is to be found as the sole field of another object, like in:

{ id: { key: 3 }, name: "Somebody" }

Constructors

WithEntityNestedId 

Instances

Instances details
(Generic t, (sch :/: sty) ~ 'DRecord name (nestedIdArg ': args), nestedIdArg ~ 'FieldDef fname k, ToSchemaKey sch idTy k, (sch :/: idTy) ~ 'DRecord idName '[idArg], idArg ~ 'FieldDef idArgName ('TPrimitive Int64 :: FieldTypeB Type Symbol), Rep t ~ D1 dInfo (C1 cInfo f), GToSchemaRecord sch fmap args f, ToBackendKey (PersistEntityBackend t) t, PersistEntityBackend t ~ SqlBackend) => ToSchema (sch :: Schema Symbol Symbol) (sty :: Symbol) (WithEntityNestedId sty fmap (Entity t)) Source # 
Instance details

Defined in Mu.Adapter.Persistent

Methods

toSchema :: WithEntityNestedId sty fmap (Entity t) -> Term sch (sch :/: sty)

newtype WithEntityPlainId (ty :: Symbol) (fmap :: Mappings Symbol Symbol) a Source #

Wrapper for Entity to be used with DerivingVia. This wrappers indicates that the identifier is to be found in the schema at the same level as other fields, like in:

{ id: 3, name: "Somebody" }

Constructors

WithEntityPlainId 

Fields

Instances

Instances details
(Generic t, (sch :/: sty) ~ 'DRecord name (idArg ': args), idArg ~ 'FieldDef idArgName ('TPrimitive Int64 :: FieldTypeB Type Symbol), Rep t ~ D1 dInfo (C1 cInfo f), GToSchemaRecord sch fmap args f, ToBackendKey (PersistEntityBackend t) t, PersistEntityBackend t ~ SqlBackend) => ToSchema (sch :: Schema Symbol Symbol) (sty :: Symbol) (WithEntityPlainId sty fmap (Entity t)) Source # 
Instance details

Defined in Mu.Adapter.Persistent

Methods

toSchema :: WithEntityPlainId sty fmap (Entity t) -> Term sch (sch :/: sty)

Generic utilities

runDb :: MonadIO m => SqlBackend -> ReaderT SqlBackend (NoLoggingT (ResourceT IO)) a -> m a Source #

Simple utility to execute a database operation in any monad which supports IO operations. Note that all logging messages are discarded.

data Pool a #

Instances

Instances details
Show (Pool a) 
Instance details

Defined in Data.Pool

Methods

showsPrec :: Int -> Pool a -> ShowS #

show :: Pool a -> String #

showList :: [Pool a] -> ShowS #

runDbPool :: MonadIO m => Pool SqlBackend -> ReaderT SqlBackend (NoLoggingT (ResourceT IO)) a -> m a Source #

Simple utility to execute a database operation in any monad which supports IO operations. Note that all logging messages are discarded.