{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# language PatternSynonyms #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE CPP #-}
module Database.Persist.Class.PersistEntity
( PersistEntity (..)
, tabulateEntity
, Update (..)
, BackendSpecificUpdate
, SelectOpt (..)
, Filter (..)
, FilterValue (..)
, BackendSpecificFilter
, Entity (.., Entity, entityKey, entityVal)
, recordName
, entityValues
, keyValueEntityToJSON, keyValueEntityFromJSON
, entityIdToJSON, entityIdFromJSON
, toPersistValueJSON, fromPersistValueJSON
, toPersistValueEnum, fromPersistValueEnum
, SymbolToField (..)
,
SafeToInsert
, SafeToInsertErrorMessage
) where
import Data.Functor.Constant
import Data.Aeson
( FromJSON(..)
, ToJSON(..)
, Value(Object)
, fromJSON
, object
, withObject
, (.:)
, (.=)
)
import qualified Data.Aeson.Parser as AP
import Data.Aeson.Text (encodeToTextBuilder)
import Data.Aeson.Types (Parser, Result(Error, Success))
import Data.Attoparsec.ByteString (parseOnly)
import Data.Functor.Identity
#if MIN_VERSION_aeson(2,0,0)
import qualified Data.Aeson.KeyMap as AM
#else
import qualified Data.HashMap.Strict as AM
#endif
import GHC.Records
import Data.List.NonEmpty (NonEmpty(..))
import Data.Maybe (isJust)
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.Encoding as TE
import qualified Data.Text.Lazy as LT
import qualified Data.Text.Lazy.Builder as TB
import GHC.Generics
import GHC.OverloadedLabels
import GHC.TypeLits
import Data.Kind (Type)
import Database.Persist.Class.PersistField
import Database.Persist.Names
import Database.Persist.Types.Base
class ( PersistField (Key record), ToJSON (Key record), FromJSON (Key record)
, Show (Key record), Read (Key record), Eq (Key record), Ord (Key record))
=> PersistEntity record where
type PersistEntityBackend record
data Key record
keyToValues :: Key record -> [PersistValue]
keyFromValues :: [PersistValue] -> Either Text (Key record)
persistIdField :: EntityField record (Key record)
entityDef :: proxy record -> EntityDef
data EntityField record :: Type -> Type
persistFieldDef :: EntityField record typ -> FieldDef
toPersistFields :: record -> [PersistValue]
fromPersistValues :: [PersistValue] -> Either Text record
tabulateEntityA
:: Applicative f
=> (forall a. EntityField record a -> f a)
-> f (Entity record)
data Unique record
persistUniqueKeys :: record -> [Unique record]
persistUniqueToFieldNames :: Unique record -> NonEmpty (FieldNameHS, FieldNameDB)
persistUniqueToValues :: Unique record -> [PersistValue]
fieldLens :: EntityField record field
-> (forall f. Functor f => (field -> f field) -> Entity record -> f (Entity record))
keyFromRecordM :: Maybe (record -> Key record)
keyFromRecordM = forall a. Maybe a
Nothing
tabulateEntity
:: PersistEntity record
=> (forall a. EntityField record a -> a)
-> Entity record
tabulateEntity :: forall record.
PersistEntity record =>
(forall a. EntityField record a -> a) -> Entity record
tabulateEntity forall a. EntityField record a -> a
fromField =
forall a. Identity a -> a
runIdentity (forall record (f :: * -> *).
(PersistEntity record, Applicative f) =>
(forall a. EntityField record a -> f a) -> f (Entity record)
tabulateEntityA (forall a. a -> Identity a
Identity forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. EntityField record a -> a
fromField))
type family BackendSpecificUpdate backend record
recordName
:: (PersistEntity record)
=> record -> Text
recordName :: forall record. PersistEntity record => record -> Text
recordName = EntityNameHS -> Text
unEntityNameHS forall b c a. (b -> c) -> (a -> b) -> a -> c
. EntityDef -> EntityNameHS
entityHaskell forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall record (proxy :: * -> *).
PersistEntity record =>
proxy record -> EntityDef
entityDef forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Maybe a
Just
data Update record = forall typ. PersistField typ => Update
{ ()
updateField :: EntityField record typ
, ()
updateValue :: typ
, forall record. Update record -> PersistUpdate
updateUpdate :: PersistUpdate
}
| BackendUpdate
(BackendSpecificUpdate (PersistEntityBackend record) record)
data SelectOpt record = forall typ. Asc (EntityField record typ)
| forall typ. Desc (EntityField record typ)
| OffsetBy Int
| LimitTo Int
type family BackendSpecificFilter backend record
data Filter record = forall typ. PersistField typ => Filter
{ ()
filterField :: EntityField record typ
, ()
filterValue :: FilterValue typ
, forall record. Filter record -> PersistFilter
filterFilter :: PersistFilter
}
| FilterAnd [Filter record]
| FilterOr [Filter record]
| BackendFilter
(BackendSpecificFilter (PersistEntityBackend record) record)
data FilterValue typ where
FilterValue :: typ -> FilterValue typ
FilterValues :: [typ] -> FilterValue typ
UnsafeValue :: forall a typ. PersistField a => a -> FilterValue typ
data Entity record =
Entity
{ forall record. Entity record -> Key record
entityKey :: Key record
, forall record. Entity record -> record
entityVal :: record
}
deriving instance (Generic (Key record), Generic record) => Generic (Entity record)
deriving instance (Eq (Key record), Eq record) => Eq (Entity record)
deriving instance (Ord (Key record), Ord record) => Ord (Entity record)
deriving instance (Show (Key record), Show record) => Show (Entity record)
deriving instance (Read (Key record), Read record) => Read (Entity record)
entityValues :: PersistEntity record => Entity record -> [PersistValue]
entityValues :: forall record.
PersistEntity record =>
Entity record -> [PersistValue]
entityValues (Entity Key record
k record
record) =
if forall a. Maybe a -> Bool
isJust (EntityDef -> Maybe CompositeDef
entityPrimary EntityDef
ent)
then
forall a b. (a -> b) -> [a] -> [b]
map forall a. PersistField a => a -> PersistValue
toPersistValue (forall record. PersistEntity record => record -> [PersistValue]
toPersistFields record
record)
else
forall record. PersistEntity record => Key record -> [PersistValue]
keyToValues Key record
k forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall a. PersistField a => a -> PersistValue
toPersistValue (forall record. PersistEntity record => record -> [PersistValue]
toPersistFields record
record)
where
ent :: EntityDef
ent = forall record (proxy :: * -> *).
PersistEntity record =>
proxy record -> EntityDef
entityDef forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just record
record
keyValueEntityToJSON :: (PersistEntity record, ToJSON record)
=> Entity record -> Value
keyValueEntityToJSON :: forall record.
(PersistEntity record, ToJSON record) =>
Entity record -> Value
keyValueEntityToJSON (Entity Key record
key record
value) = [Pair] -> Value
object
[ Key
"key" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Key record
key
, Key
"value" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= record
value
]
keyValueEntityFromJSON :: (PersistEntity record, FromJSON record)
=> Value -> Parser (Entity record)
keyValueEntityFromJSON :: forall record.
(PersistEntity record, FromJSON record) =>
Value -> Parser (Entity record)
keyValueEntityFromJSON (Object Object
o) = forall record. Key record -> record -> Entity record
Entity
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"key"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"value"
keyValueEntityFromJSON Value
_ = forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"keyValueEntityFromJSON: not an object"
entityIdToJSON :: (PersistEntity record, ToJSON record) => Entity record -> Value
entityIdToJSON :: forall record.
(PersistEntity record, ToJSON record) =>
Entity record -> Value
entityIdToJSON (Entity Key record
key record
value) = case forall a. ToJSON a => a -> Value
toJSON record
value of
Object Object
o -> Object -> Value
Object forall a b. (a -> b) -> a -> b
$ forall v. Key -> v -> KeyMap v -> KeyMap v
AM.insert Key
"id" (forall a. ToJSON a => a -> Value
toJSON Key record
key) Object
o
Value
x -> Value
x
entityIdFromJSON :: (PersistEntity record, FromJSON record) => Value -> Parser (Entity record)
entityIdFromJSON :: forall record.
(PersistEntity record, FromJSON record) =>
Value -> Parser (Entity record)
entityIdFromJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"entityIdFromJSON" forall a b. (a -> b) -> a -> b
$ \Object
o -> do
record
val <- forall a. FromJSON a => Value -> Parser a
parseJSON (Object -> Value
Object Object
o)
Key record
k <- case forall record. PersistEntity record => Maybe (record -> Key record)
keyFromRecordM of
Maybe (record -> Key record)
Nothing ->
Object
o forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id"
Just record -> Key record
func ->
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ record -> Key record
func record
val
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall record. Key record -> record -> Entity record
Entity Key record
k record
val
instance (PersistEntity record, PersistField record, PersistField (Key record))
=> PersistField (Entity record) where
toPersistValue :: Entity record -> PersistValue
toPersistValue (Entity Key record
key record
value) = case forall a. PersistField a => a -> PersistValue
toPersistValue record
value of
(PersistMap [(Text, PersistValue)]
alist) -> [(Text, PersistValue)] -> PersistValue
PersistMap ((Text
idField, forall a. PersistField a => a -> PersistValue
toPersistValue Key record
key) forall a. a -> [a] -> [a]
: [(Text, PersistValue)]
alist)
PersistValue
_ -> forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack forall a b. (a -> b) -> a -> b
$ Text -> Text
errMsg Text
"expected PersistMap"
fromPersistValue :: PersistValue -> Either Text (Entity record)
fromPersistValue (PersistMap [(Text, PersistValue)]
alist) = case [(Text, PersistValue)]
after of
[] -> forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ Text -> Text
errMsg forall a b. (a -> b) -> a -> b
$ Text
"did not find " forall a. Monoid a => a -> a -> a
`mappend` Text
idField forall a. Monoid a => a -> a -> a
`mappend` Text
" field"
(Text
"_id", PersistValue
kv):[(Text, PersistValue)]
afterRest ->
forall a. PersistField a => PersistValue -> Either Text a
fromPersistValue ([(Text, PersistValue)] -> PersistValue
PersistMap ([(Text, PersistValue)]
before forall a. [a] -> [a] -> [a]
++ [(Text, PersistValue)]
afterRest)) forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \record
record ->
forall record.
PersistEntity record =>
[PersistValue] -> Either Text (Key record)
keyFromValues [PersistValue
kv] forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Key record
k ->
forall a b. b -> Either a b
Right (forall record. Key record -> record -> Entity record
Entity Key record
k record
record)
[(Text, PersistValue)]
_ -> forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ Text -> Text
errMsg forall a b. (a -> b) -> a -> b
$ Text
"impossible id field: " forall a. Monoid a => a -> a -> a
`mappend` String -> Text
T.pack (forall a. Show a => a -> String
show [(Text, PersistValue)]
alist)
where
([(Text, PersistValue)]
before, [(Text, PersistValue)]
after) = forall a. (a -> Bool) -> [a] -> ([a], [a])
break ((forall a. Eq a => a -> a -> Bool
== Text
idField) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst) [(Text, PersistValue)]
alist
fromPersistValue PersistValue
x = forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$
Text -> Text
errMsg Text
"Expected PersistMap, received: " forall a. Monoid a => a -> a -> a
`mappend` String -> Text
T.pack (forall a. Show a => a -> String
show PersistValue
x)
errMsg :: Text -> Text
errMsg :: Text -> Text
errMsg = forall a. Monoid a => a -> a -> a
mappend Text
"PersistField entity fromPersistValue: "
idField :: Text
idField :: Text
idField = Text
"_id"
toPersistValueJSON :: ToJSON a => a -> PersistValue
toPersistValueJSON :: forall a. ToJSON a => a -> PersistValue
toPersistValueJSON = Text -> PersistValue
PersistText forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
LT.toStrict forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> Text
TB.toLazyText forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToJSON a => a -> Builder
encodeToTextBuilder forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToJSON a => a -> Value
toJSON
fromPersistValueJSON :: FromJSON a => PersistValue -> Either Text a
fromPersistValueJSON :: forall a. FromJSON a => PersistValue -> Either Text a
fromPersistValueJSON PersistValue
z = case PersistValue
z of
PersistByteString ByteString
bs -> forall {t} {a} {b}. (t -> a) -> Either t b -> Either a b
mapLeft (Text -> Text -> Text
T.append Text
"Could not parse the JSON (was a PersistByteString): ")
forall a b. (a -> b) -> a -> b
$ forall {b}. FromJSON b => ByteString -> Either Text b
parseGo ByteString
bs
PersistText Text
t -> forall {t} {a} {b}. (t -> a) -> Either t b -> Either a b
mapLeft (Text -> Text -> Text
T.append Text
"Could not parse the JSON (was PersistText): ")
forall a b. (a -> b) -> a -> b
$ forall {b}. FromJSON b => ByteString -> Either Text b
parseGo (Text -> ByteString
TE.encodeUtf8 Text
t)
PersistValue
a -> forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ Text -> Text -> Text
T.append Text
"Expected PersistByteString, received: " (String -> Text
T.pack (forall a. Show a => a -> String
show PersistValue
a))
where parseGo :: ByteString -> Either Text b
parseGo ByteString
bs = forall {t} {a} {b}. (t -> a) -> Either t b -> Either a b
mapLeft String -> Text
T.pack forall a b. (a -> b) -> a -> b
$ case forall a. Parser a -> ByteString -> Either String a
parseOnly Parser Value
AP.value ByteString
bs of
Left String
err -> forall a b. a -> Either a b
Left String
err
Right Value
v -> case forall a. FromJSON a => Value -> Result a
fromJSON Value
v of
Error String
err -> forall a b. a -> Either a b
Left String
err
Success b
a -> forall a b. b -> Either a b
Right b
a
mapLeft :: (t -> a) -> Either t b -> Either a b
mapLeft t -> a
_ (Right b
a) = forall a b. b -> Either a b
Right b
a
mapLeft t -> a
f (Left t
b) = forall a b. a -> Either a b
Left (t -> a
f t
b)
toPersistValueEnum :: Enum a => a -> PersistValue
toPersistValueEnum :: forall a. Enum a => a -> PersistValue
toPersistValueEnum = forall a. PersistField a => a -> PersistValue
toPersistValue forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Enum a => a -> Int
fromEnum
fromPersistValueEnum :: (Enum a, Bounded a) => PersistValue -> Either Text a
fromPersistValueEnum :: forall a. (Enum a, Bounded a) => PersistValue -> Either Text a
fromPersistValueEnum PersistValue
v = forall a. PersistField a => PersistValue -> Either Text a
fromPersistValue PersistValue
v forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall {b}. (Enum b, Bounded b) => Int -> Either Text b
go
where go :: Int -> Either Text b
go Int
i = let res :: b
res = forall a. Enum a => Int -> a
toEnum Int
i in
if Int
i forall a. Ord a => a -> a -> Bool
>= forall a. Enum a => a -> Int
fromEnum (forall a. a -> a -> a
asTypeOf forall a. Bounded a => a
minBound b
res) Bool -> Bool -> Bool
&& Int
i forall a. Ord a => a -> a -> Bool
<= forall a. Enum a => a -> Int
fromEnum (forall a. a -> a -> a
asTypeOf forall a. Bounded a => a
maxBound b
res)
then forall a b. b -> Either a b
Right b
res
else forall a b. a -> Either a b
Left (Text
"The number " forall a. Monoid a => a -> a -> a
`mappend` String -> Text
T.pack (forall a. Show a => a -> String
show Int
i) forall a. Monoid a => a -> a -> a
`mappend` Text
" was out of the "
forall a. Monoid a => a -> a -> a
`mappend` Text
"allowed bounds for an enum type")
class SymbolToField (sym :: Symbol) rec typ | sym rec -> typ where
symbolToField :: EntityField rec typ
instance SymbolToField sym rec typ => IsLabel sym (EntityField rec typ) where
fromLabel :: EntityField rec typ
fromLabel = forall (sym :: Symbol) rec typ.
SymbolToField sym rec typ =>
EntityField rec typ
symbolToField @sym
class SafeToInsert a where
type SafeToInsertErrorMessage a
= 'Text "The PersistEntity " ':<>: ShowType a ':<>: 'Text " does not have a default primary key."
':$$: 'Text "This means that 'insert' will fail with a database error."
':$$: 'Text "Please provide a default= clause inthe entity definition,"
':$$: 'Text "or use 'insertKey' instead to provide one."
instance (TypeError (FunctionErrorMessage a b)) => SafeToInsert (a -> b)
type FunctionErrorMessage a b =
'Text "Uh oh! It looks like you are trying to insert a function into the database."
':$$: 'Text "Argument: " ':<>: 'ShowType a
':$$: 'Text "Result: " ':<>: 'ShowType b
':$$: 'Text "You probably need to add more arguments to an Entity construction."
type EntityErrorMessage a =
'Text "It looks like you're trying to `insert` an `Entity " ':<>: 'ShowType a ':<>: 'Text "` directly."
':$$: 'Text "You want `insertKey` instead. As an example:"
':$$: 'Text " insertKey (entityKey ent) (entityVal ent)"
instance TypeError (EntityErrorMessage a) => SafeToInsert (Entity a)