{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DeriveLift #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
module Database.Persist.Types.Base
    ( module Database.Persist.Types.Base
    
    , PersistValue(..)
    , fromPersistValueText
    , LiteralType(..)
    ) where
import Control.Exception (Exception)
import Data.Char (isSpace)
import Data.List.NonEmpty (NonEmpty(..))
import qualified Data.List.NonEmpty as NEL
import Data.Map (Map)
import Data.Maybe (isNothing)
import Data.Text (Text)
import qualified Data.Text as T
import Data.Word (Word32)
import Language.Haskell.TH.Syntax (Lift(..))
import Web.HttpApiData
       ( FromHttpApiData(..)
       , ToHttpApiData(..)
       , parseBoundedTextData
       , showTextData
       )
import Web.PathPieces (PathPiece(..))
    
    
import Instances.TH.Lift ()
import Database.Persist.Names
import Database.Persist.PersistValue
data Checkmark = Active
                 
                 
               | Inactive
                 
                 
    deriving (Checkmark -> Checkmark -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Checkmark -> Checkmark -> Bool
$c/= :: Checkmark -> Checkmark -> Bool
== :: Checkmark -> Checkmark -> Bool
$c== :: Checkmark -> Checkmark -> Bool
Eq, Eq Checkmark
Checkmark -> Checkmark -> Bool
Checkmark -> Checkmark -> Ordering
Checkmark -> Checkmark -> Checkmark
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Checkmark -> Checkmark -> Checkmark
$cmin :: Checkmark -> Checkmark -> Checkmark
max :: Checkmark -> Checkmark -> Checkmark
$cmax :: Checkmark -> Checkmark -> Checkmark
>= :: Checkmark -> Checkmark -> Bool
$c>= :: Checkmark -> Checkmark -> Bool
> :: Checkmark -> Checkmark -> Bool
$c> :: Checkmark -> Checkmark -> Bool
<= :: Checkmark -> Checkmark -> Bool
$c<= :: Checkmark -> Checkmark -> Bool
< :: Checkmark -> Checkmark -> Bool
$c< :: Checkmark -> Checkmark -> Bool
compare :: Checkmark -> Checkmark -> Ordering
$ccompare :: Checkmark -> Checkmark -> Ordering
Ord, ReadPrec [Checkmark]
ReadPrec Checkmark
Int -> ReadS Checkmark
ReadS [Checkmark]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Checkmark]
$creadListPrec :: ReadPrec [Checkmark]
readPrec :: ReadPrec Checkmark
$creadPrec :: ReadPrec Checkmark
readList :: ReadS [Checkmark]
$creadList :: ReadS [Checkmark]
readsPrec :: Int -> ReadS Checkmark
$creadsPrec :: Int -> ReadS Checkmark
Read, Int -> Checkmark -> ShowS
[Checkmark] -> ShowS
Checkmark -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [Checkmark] -> ShowS
$cshowList :: [Checkmark] -> ShowS
show :: Checkmark -> [Char]
$cshow :: Checkmark -> [Char]
showsPrec :: Int -> Checkmark -> ShowS
$cshowsPrec :: Int -> Checkmark -> ShowS
Show, Int -> Checkmark
Checkmark -> Int
Checkmark -> [Checkmark]
Checkmark -> Checkmark
Checkmark -> Checkmark -> [Checkmark]
Checkmark -> Checkmark -> Checkmark -> [Checkmark]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Checkmark -> Checkmark -> Checkmark -> [Checkmark]
$cenumFromThenTo :: Checkmark -> Checkmark -> Checkmark -> [Checkmark]
enumFromTo :: Checkmark -> Checkmark -> [Checkmark]
$cenumFromTo :: Checkmark -> Checkmark -> [Checkmark]
enumFromThen :: Checkmark -> Checkmark -> [Checkmark]
$cenumFromThen :: Checkmark -> Checkmark -> [Checkmark]
enumFrom :: Checkmark -> [Checkmark]
$cenumFrom :: Checkmark -> [Checkmark]
fromEnum :: Checkmark -> Int
$cfromEnum :: Checkmark -> Int
toEnum :: Int -> Checkmark
$ctoEnum :: Int -> Checkmark
pred :: Checkmark -> Checkmark
$cpred :: Checkmark -> Checkmark
succ :: Checkmark -> Checkmark
$csucc :: Checkmark -> Checkmark
Enum, Checkmark
forall a. a -> a -> Bounded a
maxBound :: Checkmark
$cmaxBound :: Checkmark
minBound :: Checkmark
$cminBound :: Checkmark
Bounded)
instance ToHttpApiData Checkmark where
    toUrlPiece :: Checkmark -> Text
toUrlPiece = forall a. Show a => a -> Text
showTextData
instance FromHttpApiData Checkmark where
    parseUrlPiece :: Text -> Either Text Checkmark
parseUrlPiece = forall a. (Show a, Bounded a, Enum a) => Text -> Either Text a
parseBoundedTextData
instance PathPiece Checkmark where
  toPathPiece :: Checkmark -> Text
toPathPiece Checkmark
Active = Text
"active"
  toPathPiece Checkmark
Inactive = Text
"inactive"
  fromPathPiece :: Text -> Maybe Checkmark
fromPathPiece Text
"active" = forall a. a -> Maybe a
Just Checkmark
Active
  fromPathPiece Text
"inactive" = forall a. a -> Maybe a
Just Checkmark
Inactive
  fromPathPiece Text
_ = forall a. Maybe a
Nothing
data IsNullable
    = Nullable !WhyNullable
    | NotNullable
    deriving (IsNullable -> IsNullable -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IsNullable -> IsNullable -> Bool
$c/= :: IsNullable -> IsNullable -> Bool
== :: IsNullable -> IsNullable -> Bool
$c== :: IsNullable -> IsNullable -> Bool
Eq, Int -> IsNullable -> ShowS
[IsNullable] -> ShowS
IsNullable -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [IsNullable] -> ShowS
$cshowList :: [IsNullable] -> ShowS
show :: IsNullable -> [Char]
$cshow :: IsNullable -> [Char]
showsPrec :: Int -> IsNullable -> ShowS
$cshowsPrec :: Int -> IsNullable -> ShowS
Show)
fieldAttrsContainsNullable :: [FieldAttr] -> IsNullable
fieldAttrsContainsNullable :: [FieldAttr] -> IsNullable
fieldAttrsContainsNullable [FieldAttr]
s
    | FieldAttr
FieldAttrMaybe    forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [FieldAttr]
s = WhyNullable -> IsNullable
Nullable WhyNullable
ByMaybeAttr
    | FieldAttr
FieldAttrNullable forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [FieldAttr]
s = WhyNullable -> IsNullable
Nullable WhyNullable
ByNullableAttr
    | Bool
otherwise = IsNullable
NotNullable
data WhyNullable = ByMaybeAttr
                 | ByNullableAttr
                  deriving (WhyNullable -> WhyNullable -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WhyNullable -> WhyNullable -> Bool
$c/= :: WhyNullable -> WhyNullable -> Bool
== :: WhyNullable -> WhyNullable -> Bool
$c== :: WhyNullable -> WhyNullable -> Bool
Eq, Int -> WhyNullable -> ShowS
[WhyNullable] -> ShowS
WhyNullable -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [WhyNullable] -> ShowS
$cshowList :: [WhyNullable] -> ShowS
show :: WhyNullable -> [Char]
$cshow :: WhyNullable -> [Char]
showsPrec :: Int -> WhyNullable -> ShowS
$cshowsPrec :: Int -> WhyNullable -> ShowS
Show)
data EntityDef = EntityDef
    { EntityDef -> EntityNameHS
entityHaskell :: !EntityNameHS
    
    , EntityDef -> EntityNameDB
entityDB      :: !EntityNameDB
    
    , EntityDef -> EntityIdDef
entityId      :: !EntityIdDef
    
    , EntityDef -> [Text]
entityAttrs   :: ![Attr]
    
    
    
    , EntityDef -> [FieldDef]
entityFields  :: ![FieldDef]
    
    
    
    , EntityDef -> [UniqueDef]
entityUniques :: ![UniqueDef]
    
    , EntityDef -> [ForeignDef]
entityForeigns:: ![ForeignDef]
    
    
    , EntityDef -> [Text]
entityDerives :: ![Text]
    
    ,    :: !(Map Text [ExtraLine])
    , EntityDef -> Bool
entitySum     :: !Bool
    
    ,  :: !(Maybe Text)
    
    
    
    }
    deriving (Int -> EntityDef -> ShowS
[EntityDef] -> ShowS
EntityDef -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [EntityDef] -> ShowS
$cshowList :: [EntityDef] -> ShowS
show :: EntityDef -> [Char]
$cshow :: EntityDef -> [Char]
showsPrec :: Int -> EntityDef -> ShowS
$cshowsPrec :: Int -> EntityDef -> ShowS
Show, EntityDef -> EntityDef -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EntityDef -> EntityDef -> Bool
$c/= :: EntityDef -> EntityDef -> Bool
== :: EntityDef -> EntityDef -> Bool
$c== :: EntityDef -> EntityDef -> Bool
Eq, ReadPrec [EntityDef]
ReadPrec EntityDef
Int -> ReadS EntityDef
ReadS [EntityDef]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EntityDef]
$creadListPrec :: ReadPrec [EntityDef]
readPrec :: ReadPrec EntityDef
$creadPrec :: ReadPrec EntityDef
readList :: ReadS [EntityDef]
$creadList :: ReadS [EntityDef]
readsPrec :: Int -> ReadS EntityDef
$creadsPrec :: Int -> ReadS EntityDef
Read, Eq EntityDef
EntityDef -> EntityDef -> Bool
EntityDef -> EntityDef -> Ordering
EntityDef -> EntityDef -> EntityDef
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: EntityDef -> EntityDef -> EntityDef
$cmin :: EntityDef -> EntityDef -> EntityDef
max :: EntityDef -> EntityDef -> EntityDef
$cmax :: EntityDef -> EntityDef -> EntityDef
>= :: EntityDef -> EntityDef -> Bool
$c>= :: EntityDef -> EntityDef -> Bool
> :: EntityDef -> EntityDef -> Bool
$c> :: EntityDef -> EntityDef -> Bool
<= :: EntityDef -> EntityDef -> Bool
$c<= :: EntityDef -> EntityDef -> Bool
< :: EntityDef -> EntityDef -> Bool
$c< :: EntityDef -> EntityDef -> Bool
compare :: EntityDef -> EntityDef -> Ordering
$ccompare :: EntityDef -> EntityDef -> Ordering
Ord, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => EntityDef -> m Exp
forall (m :: * -> *). Quote m => EntityDef -> Code m EntityDef
liftTyped :: forall (m :: * -> *). Quote m => EntityDef -> Code m EntityDef
$cliftTyped :: forall (m :: * -> *). Quote m => EntityDef -> Code m EntityDef
lift :: forall (m :: * -> *). Quote m => EntityDef -> m Exp
$clift :: forall (m :: * -> *). Quote m => EntityDef -> m Exp
Lift)
data EntityIdDef
    = EntityIdField !FieldDef
    
    
    
    
    | EntityIdNaturalKey !CompositeDef
    
    
    
    
    
    
    deriving (Int -> EntityIdDef -> ShowS
[EntityIdDef] -> ShowS
EntityIdDef -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [EntityIdDef] -> ShowS
$cshowList :: [EntityIdDef] -> ShowS
show :: EntityIdDef -> [Char]
$cshow :: EntityIdDef -> [Char]
showsPrec :: Int -> EntityIdDef -> ShowS
$cshowsPrec :: Int -> EntityIdDef -> ShowS
Show, EntityIdDef -> EntityIdDef -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EntityIdDef -> EntityIdDef -> Bool
$c/= :: EntityIdDef -> EntityIdDef -> Bool
== :: EntityIdDef -> EntityIdDef -> Bool
$c== :: EntityIdDef -> EntityIdDef -> Bool
Eq, ReadPrec [EntityIdDef]
ReadPrec EntityIdDef
Int -> ReadS EntityIdDef
ReadS [EntityIdDef]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EntityIdDef]
$creadListPrec :: ReadPrec [EntityIdDef]
readPrec :: ReadPrec EntityIdDef
$creadPrec :: ReadPrec EntityIdDef
readList :: ReadS [EntityIdDef]
$creadList :: ReadS [EntityIdDef]
readsPrec :: Int -> ReadS EntityIdDef
$creadsPrec :: Int -> ReadS EntityIdDef
Read, Eq EntityIdDef
EntityIdDef -> EntityIdDef -> Bool
EntityIdDef -> EntityIdDef -> Ordering
EntityIdDef -> EntityIdDef -> EntityIdDef
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: EntityIdDef -> EntityIdDef -> EntityIdDef
$cmin :: EntityIdDef -> EntityIdDef -> EntityIdDef
max :: EntityIdDef -> EntityIdDef -> EntityIdDef
$cmax :: EntityIdDef -> EntityIdDef -> EntityIdDef
>= :: EntityIdDef -> EntityIdDef -> Bool
$c>= :: EntityIdDef -> EntityIdDef -> Bool
> :: EntityIdDef -> EntityIdDef -> Bool
$c> :: EntityIdDef -> EntityIdDef -> Bool
<= :: EntityIdDef -> EntityIdDef -> Bool
$c<= :: EntityIdDef -> EntityIdDef -> Bool
< :: EntityIdDef -> EntityIdDef -> Bool
$c< :: EntityIdDef -> EntityIdDef -> Bool
compare :: EntityIdDef -> EntityIdDef -> Ordering
$ccompare :: EntityIdDef -> EntityIdDef -> Ordering
Ord, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => EntityIdDef -> m Exp
forall (m :: * -> *). Quote m => EntityIdDef -> Code m EntityIdDef
liftTyped :: forall (m :: * -> *). Quote m => EntityIdDef -> Code m EntityIdDef
$cliftTyped :: forall (m :: * -> *). Quote m => EntityIdDef -> Code m EntityIdDef
lift :: forall (m :: * -> *). Quote m => EntityIdDef -> m Exp
$clift :: forall (m :: * -> *). Quote m => EntityIdDef -> m Exp
Lift)
entitiesPrimary :: EntityDef -> NonEmpty FieldDef
entitiesPrimary :: EntityDef -> NonEmpty FieldDef
entitiesPrimary EntityDef
t =
    case EntityDef -> EntityIdDef
entityId EntityDef
t of
        EntityIdNaturalKey CompositeDef
fds ->
            CompositeDef -> NonEmpty FieldDef
compositeFields CompositeDef
fds
        EntityIdField FieldDef
fd ->
            forall (f :: * -> *) a. Applicative f => a -> f a
pure FieldDef
fd
entityPrimary :: EntityDef -> Maybe CompositeDef
entityPrimary :: EntityDef -> Maybe CompositeDef
entityPrimary EntityDef
t =
    case EntityDef -> EntityIdDef
entityId EntityDef
t of
        EntityIdNaturalKey CompositeDef
c ->
            forall a. a -> Maybe a
Just CompositeDef
c
        EntityIdDef
_ ->
            forall a. Maybe a
Nothing
entityKeyFields :: EntityDef -> NonEmpty FieldDef
entityKeyFields :: EntityDef -> NonEmpty FieldDef
entityKeyFields =
    EntityDef -> NonEmpty FieldDef
entitiesPrimary
keyAndEntityFields :: EntityDef -> NonEmpty FieldDef
keyAndEntityFields :: EntityDef -> NonEmpty FieldDef
keyAndEntityFields EntityDef
ent =
    case EntityDef -> EntityIdDef
entityId EntityDef
ent of
        EntityIdField FieldDef
fd ->
            FieldDef
fd forall a. a -> [a] -> NonEmpty a
:| [FieldDef]
fields
        EntityIdNaturalKey CompositeDef
_ ->
            case forall a. [a] -> Maybe (NonEmpty a)
NEL.nonEmpty [FieldDef]
fields of
                Maybe (NonEmpty FieldDef)
Nothing ->
                    forall a. HasCallStack => [Char] -> a
error forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat
                        [ [Char]
"persistent internal guarantee failed: entity is "
                        , [Char]
"defined with an entityId = EntityIdNaturalKey, "
                        , [Char]
"but somehow doesn't have any entity fields."
                        ]
                Just NonEmpty FieldDef
xs ->
                    NonEmpty FieldDef
xs
  where
    fields :: [FieldDef]
fields = forall a. (a -> Bool) -> [a] -> [a]
filter FieldDef -> Bool
isHaskellField forall a b. (a -> b) -> a -> b
$ EntityDef -> [FieldDef]
entityFields EntityDef
ent
type  = [Text]
type Attr = Text
data FieldAttr
    = FieldAttrMaybe
    
    
    
    
    
    
    
    
    
    
    | FieldAttrNullable
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    | FieldAttrMigrationOnly
    
    
    
    
    
    
    
    
    
    
    
    
    | FieldAttrSafeToRemove
    
    
    
    
    
    
    
    
    
    
    
    
    | FieldAttrNoreference
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    | FieldAttrReference Text
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    | FieldAttrConstraint Text
    
    
    
    
    
    
    
    
    
    
    | FieldAttrDefault Text
    
    
    
    
    
    
    
    
    
    | FieldAttrSqltype Text
    
    
    
    
    
    
    
    
    | FieldAttrMaxlen Integer
    
    
    
    
    
    
    
    
    | FieldAttrSql Text
    
    
    
    
    
    
    
    
    
    | FieldAttrOther Text
    
    deriving (Int -> FieldAttr -> ShowS
[FieldAttr] -> ShowS
FieldAttr -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [FieldAttr] -> ShowS
$cshowList :: [FieldAttr] -> ShowS
show :: FieldAttr -> [Char]
$cshow :: FieldAttr -> [Char]
showsPrec :: Int -> FieldAttr -> ShowS
$cshowsPrec :: Int -> FieldAttr -> ShowS
Show, FieldAttr -> FieldAttr -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FieldAttr -> FieldAttr -> Bool
$c/= :: FieldAttr -> FieldAttr -> Bool
== :: FieldAttr -> FieldAttr -> Bool
$c== :: FieldAttr -> FieldAttr -> Bool
Eq, ReadPrec [FieldAttr]
ReadPrec FieldAttr
Int -> ReadS FieldAttr
ReadS [FieldAttr]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FieldAttr]
$creadListPrec :: ReadPrec [FieldAttr]
readPrec :: ReadPrec FieldAttr
$creadPrec :: ReadPrec FieldAttr
readList :: ReadS [FieldAttr]
$creadList :: ReadS [FieldAttr]
readsPrec :: Int -> ReadS FieldAttr
$creadsPrec :: Int -> ReadS FieldAttr
Read, Eq FieldAttr
FieldAttr -> FieldAttr -> Bool
FieldAttr -> FieldAttr -> Ordering
FieldAttr -> FieldAttr -> FieldAttr
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FieldAttr -> FieldAttr -> FieldAttr
$cmin :: FieldAttr -> FieldAttr -> FieldAttr
max :: FieldAttr -> FieldAttr -> FieldAttr
$cmax :: FieldAttr -> FieldAttr -> FieldAttr
>= :: FieldAttr -> FieldAttr -> Bool
$c>= :: FieldAttr -> FieldAttr -> Bool
> :: FieldAttr -> FieldAttr -> Bool
$c> :: FieldAttr -> FieldAttr -> Bool
<= :: FieldAttr -> FieldAttr -> Bool
$c<= :: FieldAttr -> FieldAttr -> Bool
< :: FieldAttr -> FieldAttr -> Bool
$c< :: FieldAttr -> FieldAttr -> Bool
compare :: FieldAttr -> FieldAttr -> Ordering
$ccompare :: FieldAttr -> FieldAttr -> Ordering
Ord, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => FieldAttr -> m Exp
forall (m :: * -> *). Quote m => FieldAttr -> Code m FieldAttr
liftTyped :: forall (m :: * -> *). Quote m => FieldAttr -> Code m FieldAttr
$cliftTyped :: forall (m :: * -> *). Quote m => FieldAttr -> Code m FieldAttr
lift :: forall (m :: * -> *). Quote m => FieldAttr -> m Exp
$clift :: forall (m :: * -> *). Quote m => FieldAttr -> m Exp
Lift)
parseFieldAttrs :: [Text] -> [FieldAttr]
parseFieldAttrs :: [Text] -> [FieldAttr]
parseFieldAttrs = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. (a -> b) -> a -> b
$ \case
    Text
"Maybe" -> FieldAttr
FieldAttrMaybe
    Text
"nullable" -> FieldAttr
FieldAttrNullable
    Text
"MigrationOnly" -> FieldAttr
FieldAttrMigrationOnly
    Text
"SafeToRemove" -> FieldAttr
FieldAttrSafeToRemove
    Text
"noreference" -> FieldAttr
FieldAttrNoreference
    Text
raw
        | Just Text
x <- Text -> Text -> Maybe Text
T.stripPrefix Text
"reference=" Text
raw -> Text -> FieldAttr
FieldAttrReference Text
x
        | Just Text
x <- Text -> Text -> Maybe Text
T.stripPrefix Text
"constraint=" Text
raw -> Text -> FieldAttr
FieldAttrConstraint Text
x
        | Just Text
x <- Text -> Text -> Maybe Text
T.stripPrefix Text
"default=" Text
raw -> Text -> FieldAttr
FieldAttrDefault Text
x
        | Just Text
x <- Text -> Text -> Maybe Text
T.stripPrefix Text
"sqltype=" Text
raw -> Text -> FieldAttr
FieldAttrSqltype Text
x
        | Just Text
x <- Text -> Text -> Maybe Text
T.stripPrefix Text
"maxlen=" Text
raw -> case forall a. Read a => ReadS a
reads (Text -> [Char]
T.unpack Text
x) of
            [(Integer
n, [Char]
s)] | forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Char -> Bool
isSpace [Char]
s -> Integer -> FieldAttr
FieldAttrMaxlen Integer
n
            [(Integer, [Char])]
_ -> forall a. HasCallStack => [Char] -> a
error forall a b. (a -> b) -> a -> b
$ [Char]
"Could not parse maxlen field with value " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> [Char]
show Text
raw
        | Just Text
x <- Text -> Text -> Maybe Text
T.stripPrefix Text
"sql=" Text
raw ->
            Text -> FieldAttr
FieldAttrSql Text
x
        | Bool
otherwise -> Text -> FieldAttr
FieldAttrOther Text
raw
data FieldType
    = FTTypeCon (Maybe Text) Text
    
    | FTLit FieldTypeLit
    | FTTypePromoted Text
    | FTApp FieldType FieldType
    | FTList FieldType
    deriving (Int -> FieldType -> ShowS
[FieldType] -> ShowS
FieldType -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [FieldType] -> ShowS
$cshowList :: [FieldType] -> ShowS
show :: FieldType -> [Char]
$cshow :: FieldType -> [Char]
showsPrec :: Int -> FieldType -> ShowS
$cshowsPrec :: Int -> FieldType -> ShowS
Show, FieldType -> FieldType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FieldType -> FieldType -> Bool
$c/= :: FieldType -> FieldType -> Bool
== :: FieldType -> FieldType -> Bool
$c== :: FieldType -> FieldType -> Bool
Eq, ReadPrec [FieldType]
ReadPrec FieldType
Int -> ReadS FieldType
ReadS [FieldType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FieldType]
$creadListPrec :: ReadPrec [FieldType]
readPrec :: ReadPrec FieldType
$creadPrec :: ReadPrec FieldType
readList :: ReadS [FieldType]
$creadList :: ReadS [FieldType]
readsPrec :: Int -> ReadS FieldType
$creadsPrec :: Int -> ReadS FieldType
Read, Eq FieldType
FieldType -> FieldType -> Bool
FieldType -> FieldType -> Ordering
FieldType -> FieldType -> FieldType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FieldType -> FieldType -> FieldType
$cmin :: FieldType -> FieldType -> FieldType
max :: FieldType -> FieldType -> FieldType
$cmax :: FieldType -> FieldType -> FieldType
>= :: FieldType -> FieldType -> Bool
$c>= :: FieldType -> FieldType -> Bool
> :: FieldType -> FieldType -> Bool
$c> :: FieldType -> FieldType -> Bool
<= :: FieldType -> FieldType -> Bool
$c<= :: FieldType -> FieldType -> Bool
< :: FieldType -> FieldType -> Bool
$c< :: FieldType -> FieldType -> Bool
compare :: FieldType -> FieldType -> Ordering
$ccompare :: FieldType -> FieldType -> Ordering
Ord, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => FieldType -> m Exp
forall (m :: * -> *). Quote m => FieldType -> Code m FieldType
liftTyped :: forall (m :: * -> *). Quote m => FieldType -> Code m FieldType
$cliftTyped :: forall (m :: * -> *). Quote m => FieldType -> Code m FieldType
lift :: forall (m :: * -> *). Quote m => FieldType -> m Exp
$clift :: forall (m :: * -> *). Quote m => FieldType -> m Exp
Lift)
data FieldTypeLit
    = IntTypeLit Integer
    | TextTypeLit Text
    deriving (Int -> FieldTypeLit -> ShowS
[FieldTypeLit] -> ShowS
FieldTypeLit -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [FieldTypeLit] -> ShowS
$cshowList :: [FieldTypeLit] -> ShowS
show :: FieldTypeLit -> [Char]
$cshow :: FieldTypeLit -> [Char]
showsPrec :: Int -> FieldTypeLit -> ShowS
$cshowsPrec :: Int -> FieldTypeLit -> ShowS
Show, FieldTypeLit -> FieldTypeLit -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FieldTypeLit -> FieldTypeLit -> Bool
$c/= :: FieldTypeLit -> FieldTypeLit -> Bool
== :: FieldTypeLit -> FieldTypeLit -> Bool
$c== :: FieldTypeLit -> FieldTypeLit -> Bool
Eq, ReadPrec [FieldTypeLit]
ReadPrec FieldTypeLit
Int -> ReadS FieldTypeLit
ReadS [FieldTypeLit]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FieldTypeLit]
$creadListPrec :: ReadPrec [FieldTypeLit]
readPrec :: ReadPrec FieldTypeLit
$creadPrec :: ReadPrec FieldTypeLit
readList :: ReadS [FieldTypeLit]
$creadList :: ReadS [FieldTypeLit]
readsPrec :: Int -> ReadS FieldTypeLit
$creadsPrec :: Int -> ReadS FieldTypeLit
Read, Eq FieldTypeLit
FieldTypeLit -> FieldTypeLit -> Bool
FieldTypeLit -> FieldTypeLit -> Ordering
FieldTypeLit -> FieldTypeLit -> FieldTypeLit
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FieldTypeLit -> FieldTypeLit -> FieldTypeLit
$cmin :: FieldTypeLit -> FieldTypeLit -> FieldTypeLit
max :: FieldTypeLit -> FieldTypeLit -> FieldTypeLit
$cmax :: FieldTypeLit -> FieldTypeLit -> FieldTypeLit
>= :: FieldTypeLit -> FieldTypeLit -> Bool
$c>= :: FieldTypeLit -> FieldTypeLit -> Bool
> :: FieldTypeLit -> FieldTypeLit -> Bool
$c> :: FieldTypeLit -> FieldTypeLit -> Bool
<= :: FieldTypeLit -> FieldTypeLit -> Bool
$c<= :: FieldTypeLit -> FieldTypeLit -> Bool
< :: FieldTypeLit -> FieldTypeLit -> Bool
$c< :: FieldTypeLit -> FieldTypeLit -> Bool
compare :: FieldTypeLit -> FieldTypeLit -> Ordering
$ccompare :: FieldTypeLit -> FieldTypeLit -> Ordering
Ord, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => FieldTypeLit -> m Exp
forall (m :: * -> *).
Quote m =>
FieldTypeLit -> Code m FieldTypeLit
liftTyped :: forall (m :: * -> *).
Quote m =>
FieldTypeLit -> Code m FieldTypeLit
$cliftTyped :: forall (m :: * -> *).
Quote m =>
FieldTypeLit -> Code m FieldTypeLit
lift :: forall (m :: * -> *). Quote m => FieldTypeLit -> m Exp
$clift :: forall (m :: * -> *). Quote m => FieldTypeLit -> m Exp
Lift)
isFieldNotGenerated :: FieldDef -> Bool
isFieldNotGenerated :: FieldDef -> Bool
isFieldNotGenerated = forall a. Maybe a -> Bool
isNothing forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldDef -> Maybe Text
fieldGenerated
data ReferenceDef
    = NoReference
    | ForeignRef !EntityNameHS
    
    
    | EmbedRef EntityNameHS
    | SelfReference
    
    deriving (Int -> ReferenceDef -> ShowS
[ReferenceDef] -> ShowS
ReferenceDef -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [ReferenceDef] -> ShowS
$cshowList :: [ReferenceDef] -> ShowS
show :: ReferenceDef -> [Char]
$cshow :: ReferenceDef -> [Char]
showsPrec :: Int -> ReferenceDef -> ShowS
$cshowsPrec :: Int -> ReferenceDef -> ShowS
Show, ReferenceDef -> ReferenceDef -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReferenceDef -> ReferenceDef -> Bool
$c/= :: ReferenceDef -> ReferenceDef -> Bool
== :: ReferenceDef -> ReferenceDef -> Bool
$c== :: ReferenceDef -> ReferenceDef -> Bool
Eq, ReadPrec [ReferenceDef]
ReadPrec ReferenceDef
Int -> ReadS ReferenceDef
ReadS [ReferenceDef]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ReferenceDef]
$creadListPrec :: ReadPrec [ReferenceDef]
readPrec :: ReadPrec ReferenceDef
$creadPrec :: ReadPrec ReferenceDef
readList :: ReadS [ReferenceDef]
$creadList :: ReadS [ReferenceDef]
readsPrec :: Int -> ReadS ReferenceDef
$creadsPrec :: Int -> ReadS ReferenceDef
Read, Eq ReferenceDef
ReferenceDef -> ReferenceDef -> Bool
ReferenceDef -> ReferenceDef -> Ordering
ReferenceDef -> ReferenceDef -> ReferenceDef
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ReferenceDef -> ReferenceDef -> ReferenceDef
$cmin :: ReferenceDef -> ReferenceDef -> ReferenceDef
max :: ReferenceDef -> ReferenceDef -> ReferenceDef
$cmax :: ReferenceDef -> ReferenceDef -> ReferenceDef
>= :: ReferenceDef -> ReferenceDef -> Bool
$c>= :: ReferenceDef -> ReferenceDef -> Bool
> :: ReferenceDef -> ReferenceDef -> Bool
$c> :: ReferenceDef -> ReferenceDef -> Bool
<= :: ReferenceDef -> ReferenceDef -> Bool
$c<= :: ReferenceDef -> ReferenceDef -> Bool
< :: ReferenceDef -> ReferenceDef -> Bool
$c< :: ReferenceDef -> ReferenceDef -> Bool
compare :: ReferenceDef -> ReferenceDef -> Ordering
$ccompare :: ReferenceDef -> ReferenceDef -> Ordering
Ord, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => ReferenceDef -> m Exp
forall (m :: * -> *).
Quote m =>
ReferenceDef -> Code m ReferenceDef
liftTyped :: forall (m :: * -> *).
Quote m =>
ReferenceDef -> Code m ReferenceDef
$cliftTyped :: forall (m :: * -> *).
Quote m =>
ReferenceDef -> Code m ReferenceDef
lift :: forall (m :: * -> *). Quote m => ReferenceDef -> m Exp
$clift :: forall (m :: * -> *). Quote m => ReferenceDef -> m Exp
Lift)
data EmbedEntityDef = EmbedEntityDef
    { EmbedEntityDef -> EntityNameHS
embeddedHaskell :: EntityNameHS
    , EmbedEntityDef -> [EmbedFieldDef]
embeddedFields  :: [EmbedFieldDef]
    } deriving (Int -> EmbedEntityDef -> ShowS
[EmbedEntityDef] -> ShowS
EmbedEntityDef -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [EmbedEntityDef] -> ShowS
$cshowList :: [EmbedEntityDef] -> ShowS
show :: EmbedEntityDef -> [Char]
$cshow :: EmbedEntityDef -> [Char]
showsPrec :: Int -> EmbedEntityDef -> ShowS
$cshowsPrec :: Int -> EmbedEntityDef -> ShowS
Show, EmbedEntityDef -> EmbedEntityDef -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EmbedEntityDef -> EmbedEntityDef -> Bool
$c/= :: EmbedEntityDef -> EmbedEntityDef -> Bool
== :: EmbedEntityDef -> EmbedEntityDef -> Bool
$c== :: EmbedEntityDef -> EmbedEntityDef -> Bool
Eq, ReadPrec [EmbedEntityDef]
ReadPrec EmbedEntityDef
Int -> ReadS EmbedEntityDef
ReadS [EmbedEntityDef]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EmbedEntityDef]
$creadListPrec :: ReadPrec [EmbedEntityDef]
readPrec :: ReadPrec EmbedEntityDef
$creadPrec :: ReadPrec EmbedEntityDef
readList :: ReadS [EmbedEntityDef]
$creadList :: ReadS [EmbedEntityDef]
readsPrec :: Int -> ReadS EmbedEntityDef
$creadsPrec :: Int -> ReadS EmbedEntityDef
Read, Eq EmbedEntityDef
EmbedEntityDef -> EmbedEntityDef -> Bool
EmbedEntityDef -> EmbedEntityDef -> Ordering
EmbedEntityDef -> EmbedEntityDef -> EmbedEntityDef
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: EmbedEntityDef -> EmbedEntityDef -> EmbedEntityDef
$cmin :: EmbedEntityDef -> EmbedEntityDef -> EmbedEntityDef
max :: EmbedEntityDef -> EmbedEntityDef -> EmbedEntityDef
$cmax :: EmbedEntityDef -> EmbedEntityDef -> EmbedEntityDef
>= :: EmbedEntityDef -> EmbedEntityDef -> Bool
$c>= :: EmbedEntityDef -> EmbedEntityDef -> Bool
> :: EmbedEntityDef -> EmbedEntityDef -> Bool
$c> :: EmbedEntityDef -> EmbedEntityDef -> Bool
<= :: EmbedEntityDef -> EmbedEntityDef -> Bool
$c<= :: EmbedEntityDef -> EmbedEntityDef -> Bool
< :: EmbedEntityDef -> EmbedEntityDef -> Bool
$c< :: EmbedEntityDef -> EmbedEntityDef -> Bool
compare :: EmbedEntityDef -> EmbedEntityDef -> Ordering
$ccompare :: EmbedEntityDef -> EmbedEntityDef -> Ordering
Ord, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => EmbedEntityDef -> m Exp
forall (m :: * -> *).
Quote m =>
EmbedEntityDef -> Code m EmbedEntityDef
liftTyped :: forall (m :: * -> *).
Quote m =>
EmbedEntityDef -> Code m EmbedEntityDef
$cliftTyped :: forall (m :: * -> *).
Quote m =>
EmbedEntityDef -> Code m EmbedEntityDef
lift :: forall (m :: * -> *). Quote m => EmbedEntityDef -> m Exp
$clift :: forall (m :: * -> *). Quote m => EmbedEntityDef -> m Exp
Lift)
data EmbedFieldDef = EmbedFieldDef
    { EmbedFieldDef -> FieldNameDB
emFieldDB    :: FieldNameDB
    , EmbedFieldDef -> Maybe (Either SelfEmbed EntityNameHS)
emFieldEmbed :: Maybe (Either SelfEmbed EntityNameHS)
    }
    deriving (Int -> EmbedFieldDef -> ShowS
[EmbedFieldDef] -> ShowS
EmbedFieldDef -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [EmbedFieldDef] -> ShowS
$cshowList :: [EmbedFieldDef] -> ShowS
show :: EmbedFieldDef -> [Char]
$cshow :: EmbedFieldDef -> [Char]
showsPrec :: Int -> EmbedFieldDef -> ShowS
$cshowsPrec :: Int -> EmbedFieldDef -> ShowS
Show, EmbedFieldDef -> EmbedFieldDef -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EmbedFieldDef -> EmbedFieldDef -> Bool
$c/= :: EmbedFieldDef -> EmbedFieldDef -> Bool
== :: EmbedFieldDef -> EmbedFieldDef -> Bool
$c== :: EmbedFieldDef -> EmbedFieldDef -> Bool
Eq, ReadPrec [EmbedFieldDef]
ReadPrec EmbedFieldDef
Int -> ReadS EmbedFieldDef
ReadS [EmbedFieldDef]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EmbedFieldDef]
$creadListPrec :: ReadPrec [EmbedFieldDef]
readPrec :: ReadPrec EmbedFieldDef
$creadPrec :: ReadPrec EmbedFieldDef
readList :: ReadS [EmbedFieldDef]
$creadList :: ReadS [EmbedFieldDef]
readsPrec :: Int -> ReadS EmbedFieldDef
$creadsPrec :: Int -> ReadS EmbedFieldDef
Read, Eq EmbedFieldDef
EmbedFieldDef -> EmbedFieldDef -> Bool
EmbedFieldDef -> EmbedFieldDef -> Ordering
EmbedFieldDef -> EmbedFieldDef -> EmbedFieldDef
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: EmbedFieldDef -> EmbedFieldDef -> EmbedFieldDef
$cmin :: EmbedFieldDef -> EmbedFieldDef -> EmbedFieldDef
max :: EmbedFieldDef -> EmbedFieldDef -> EmbedFieldDef
$cmax :: EmbedFieldDef -> EmbedFieldDef -> EmbedFieldDef
>= :: EmbedFieldDef -> EmbedFieldDef -> Bool
$c>= :: EmbedFieldDef -> EmbedFieldDef -> Bool
> :: EmbedFieldDef -> EmbedFieldDef -> Bool
$c> :: EmbedFieldDef -> EmbedFieldDef -> Bool
<= :: EmbedFieldDef -> EmbedFieldDef -> Bool
$c<= :: EmbedFieldDef -> EmbedFieldDef -> Bool
< :: EmbedFieldDef -> EmbedFieldDef -> Bool
$c< :: EmbedFieldDef -> EmbedFieldDef -> Bool
compare :: EmbedFieldDef -> EmbedFieldDef -> Ordering
$ccompare :: EmbedFieldDef -> EmbedFieldDef -> Ordering
Ord, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => EmbedFieldDef -> m Exp
forall (m :: * -> *).
Quote m =>
EmbedFieldDef -> Code m EmbedFieldDef
liftTyped :: forall (m :: * -> *).
Quote m =>
EmbedFieldDef -> Code m EmbedFieldDef
$cliftTyped :: forall (m :: * -> *).
Quote m =>
EmbedFieldDef -> Code m EmbedFieldDef
lift :: forall (m :: * -> *). Quote m => EmbedFieldDef -> m Exp
$clift :: forall (m :: * -> *). Quote m => EmbedFieldDef -> m Exp
Lift)
data SelfEmbed = SelfEmbed
    deriving (Int -> SelfEmbed -> ShowS
[SelfEmbed] -> ShowS
SelfEmbed -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [SelfEmbed] -> ShowS
$cshowList :: [SelfEmbed] -> ShowS
show :: SelfEmbed -> [Char]
$cshow :: SelfEmbed -> [Char]
showsPrec :: Int -> SelfEmbed -> ShowS
$cshowsPrec :: Int -> SelfEmbed -> ShowS
Show, SelfEmbed -> SelfEmbed -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SelfEmbed -> SelfEmbed -> Bool
$c/= :: SelfEmbed -> SelfEmbed -> Bool
== :: SelfEmbed -> SelfEmbed -> Bool
$c== :: SelfEmbed -> SelfEmbed -> Bool
Eq, ReadPrec [SelfEmbed]
ReadPrec SelfEmbed
Int -> ReadS SelfEmbed
ReadS [SelfEmbed]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SelfEmbed]
$creadListPrec :: ReadPrec [SelfEmbed]
readPrec :: ReadPrec SelfEmbed
$creadPrec :: ReadPrec SelfEmbed
readList :: ReadS [SelfEmbed]
$creadList :: ReadS [SelfEmbed]
readsPrec :: Int -> ReadS SelfEmbed
$creadsPrec :: Int -> ReadS SelfEmbed
Read, Eq SelfEmbed
SelfEmbed -> SelfEmbed -> Bool
SelfEmbed -> SelfEmbed -> Ordering
SelfEmbed -> SelfEmbed -> SelfEmbed
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SelfEmbed -> SelfEmbed -> SelfEmbed
$cmin :: SelfEmbed -> SelfEmbed -> SelfEmbed
max :: SelfEmbed -> SelfEmbed -> SelfEmbed
$cmax :: SelfEmbed -> SelfEmbed -> SelfEmbed
>= :: SelfEmbed -> SelfEmbed -> Bool
$c>= :: SelfEmbed -> SelfEmbed -> Bool
> :: SelfEmbed -> SelfEmbed -> Bool
$c> :: SelfEmbed -> SelfEmbed -> Bool
<= :: SelfEmbed -> SelfEmbed -> Bool
$c<= :: SelfEmbed -> SelfEmbed -> Bool
< :: SelfEmbed -> SelfEmbed -> Bool
$c< :: SelfEmbed -> SelfEmbed -> Bool
compare :: SelfEmbed -> SelfEmbed -> Ordering
$ccompare :: SelfEmbed -> SelfEmbed -> Ordering
Ord, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => SelfEmbed -> m Exp
forall (m :: * -> *). Quote m => SelfEmbed -> Code m SelfEmbed
liftTyped :: forall (m :: * -> *). Quote m => SelfEmbed -> Code m SelfEmbed
$cliftTyped :: forall (m :: * -> *). Quote m => SelfEmbed -> Code m SelfEmbed
lift :: forall (m :: * -> *). Quote m => SelfEmbed -> m Exp
$clift :: forall (m :: * -> *). Quote m => SelfEmbed -> m Exp
Lift)
isHaskellField :: FieldDef -> Bool
isHaskellField :: FieldDef -> Bool
isHaskellField FieldDef
fd =
    FieldAttr
FieldAttrMigrationOnly forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` FieldDef -> [FieldAttr]
fieldAttrs FieldDef
fd Bool -> Bool -> Bool
&&
    FieldAttr
FieldAttrSafeToRemove forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` FieldDef -> [FieldAttr]
fieldAttrs FieldDef
fd
toEmbedEntityDef :: EntityDef -> EmbedEntityDef
toEmbedEntityDef :: EntityDef -> EmbedEntityDef
toEmbedEntityDef EntityDef
ent = EmbedEntityDef
embDef
  where
    embDef :: EmbedEntityDef
embDef = EmbedEntityDef
        { embeddedHaskell :: EntityNameHS
embeddedHaskell = EntityDef -> EntityNameHS
entityHaskell EntityDef
ent
        , embeddedFields :: [EmbedFieldDef]
embeddedFields =
            forall a b. (a -> b) -> [a] -> [b]
map FieldDef -> EmbedFieldDef
toEmbedFieldDef
            forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
filter FieldDef -> Bool
isHaskellField
            forall a b. (a -> b) -> a -> b
$ EntityDef -> [FieldDef]
entityFields EntityDef
ent
        }
    toEmbedFieldDef :: FieldDef -> EmbedFieldDef
    toEmbedFieldDef :: FieldDef -> EmbedFieldDef
toEmbedFieldDef FieldDef
field =
        EmbedFieldDef
            { emFieldDB :: FieldNameDB
emFieldDB =
                FieldDef -> FieldNameDB
fieldDB FieldDef
field
            , emFieldEmbed :: Maybe (Either SelfEmbed EntityNameHS)
emFieldEmbed =
                case FieldDef -> ReferenceDef
fieldReference FieldDef
field of
                    EmbedRef EntityNameHS
em ->
                        forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a b. b -> Either a b
Right EntityNameHS
em
                    ReferenceDef
SelfReference -> forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a b. a -> Either a b
Left SelfEmbed
SelfEmbed
                    ReferenceDef
_ -> forall a. Maybe a
Nothing
            }
data UniqueDef = UniqueDef
    { UniqueDef -> ConstraintNameHS
uniqueHaskell :: !ConstraintNameHS
    , UniqueDef -> ConstraintNameDB
uniqueDBName  :: !ConstraintNameDB
    , UniqueDef -> NonEmpty (FieldNameHS, FieldNameDB)
uniqueFields  :: !(NonEmpty (FieldNameHS, FieldNameDB))
    , UniqueDef -> [Text]
uniqueAttrs   :: ![Attr]
    }
    deriving (Int -> UniqueDef -> ShowS
[UniqueDef] -> ShowS
UniqueDef -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [UniqueDef] -> ShowS
$cshowList :: [UniqueDef] -> ShowS
show :: UniqueDef -> [Char]
$cshow :: UniqueDef -> [Char]
showsPrec :: Int -> UniqueDef -> ShowS
$cshowsPrec :: Int -> UniqueDef -> ShowS
Show, UniqueDef -> UniqueDef -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UniqueDef -> UniqueDef -> Bool
$c/= :: UniqueDef -> UniqueDef -> Bool
== :: UniqueDef -> UniqueDef -> Bool
$c== :: UniqueDef -> UniqueDef -> Bool
Eq, ReadPrec [UniqueDef]
ReadPrec UniqueDef
Int -> ReadS UniqueDef
ReadS [UniqueDef]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UniqueDef]
$creadListPrec :: ReadPrec [UniqueDef]
readPrec :: ReadPrec UniqueDef
$creadPrec :: ReadPrec UniqueDef
readList :: ReadS [UniqueDef]
$creadList :: ReadS [UniqueDef]
readsPrec :: Int -> ReadS UniqueDef
$creadsPrec :: Int -> ReadS UniqueDef
Read, Eq UniqueDef
UniqueDef -> UniqueDef -> Bool
UniqueDef -> UniqueDef -> Ordering
UniqueDef -> UniqueDef -> UniqueDef
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: UniqueDef -> UniqueDef -> UniqueDef
$cmin :: UniqueDef -> UniqueDef -> UniqueDef
max :: UniqueDef -> UniqueDef -> UniqueDef
$cmax :: UniqueDef -> UniqueDef -> UniqueDef
>= :: UniqueDef -> UniqueDef -> Bool
$c>= :: UniqueDef -> UniqueDef -> Bool
> :: UniqueDef -> UniqueDef -> Bool
$c> :: UniqueDef -> UniqueDef -> Bool
<= :: UniqueDef -> UniqueDef -> Bool
$c<= :: UniqueDef -> UniqueDef -> Bool
< :: UniqueDef -> UniqueDef -> Bool
$c< :: UniqueDef -> UniqueDef -> Bool
compare :: UniqueDef -> UniqueDef -> Ordering
$ccompare :: UniqueDef -> UniqueDef -> Ordering
Ord, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => UniqueDef -> m Exp
forall (m :: * -> *). Quote m => UniqueDef -> Code m UniqueDef
liftTyped :: forall (m :: * -> *). Quote m => UniqueDef -> Code m UniqueDef
$cliftTyped :: forall (m :: * -> *). Quote m => UniqueDef -> Code m UniqueDef
lift :: forall (m :: * -> *). Quote m => UniqueDef -> m Exp
$clift :: forall (m :: * -> *). Quote m => UniqueDef -> m Exp
Lift)
data CompositeDef = CompositeDef
    { CompositeDef -> NonEmpty FieldDef
compositeFields  :: !(NonEmpty FieldDef)
    , CompositeDef -> [Text]
compositeAttrs   :: ![Attr]
    }
    deriving (Int -> CompositeDef -> ShowS
[CompositeDef] -> ShowS
CompositeDef -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [CompositeDef] -> ShowS
$cshowList :: [CompositeDef] -> ShowS
show :: CompositeDef -> [Char]
$cshow :: CompositeDef -> [Char]
showsPrec :: Int -> CompositeDef -> ShowS
$cshowsPrec :: Int -> CompositeDef -> ShowS
Show, CompositeDef -> CompositeDef -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CompositeDef -> CompositeDef -> Bool
$c/= :: CompositeDef -> CompositeDef -> Bool
== :: CompositeDef -> CompositeDef -> Bool
$c== :: CompositeDef -> CompositeDef -> Bool
Eq, ReadPrec [CompositeDef]
ReadPrec CompositeDef
Int -> ReadS CompositeDef
ReadS [CompositeDef]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CompositeDef]
$creadListPrec :: ReadPrec [CompositeDef]
readPrec :: ReadPrec CompositeDef
$creadPrec :: ReadPrec CompositeDef
readList :: ReadS [CompositeDef]
$creadList :: ReadS [CompositeDef]
readsPrec :: Int -> ReadS CompositeDef
$creadsPrec :: Int -> ReadS CompositeDef
Read, Eq CompositeDef
CompositeDef -> CompositeDef -> Bool
CompositeDef -> CompositeDef -> Ordering
CompositeDef -> CompositeDef -> CompositeDef
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CompositeDef -> CompositeDef -> CompositeDef
$cmin :: CompositeDef -> CompositeDef -> CompositeDef
max :: CompositeDef -> CompositeDef -> CompositeDef
$cmax :: CompositeDef -> CompositeDef -> CompositeDef
>= :: CompositeDef -> CompositeDef -> Bool
$c>= :: CompositeDef -> CompositeDef -> Bool
> :: CompositeDef -> CompositeDef -> Bool
$c> :: CompositeDef -> CompositeDef -> Bool
<= :: CompositeDef -> CompositeDef -> Bool
$c<= :: CompositeDef -> CompositeDef -> Bool
< :: CompositeDef -> CompositeDef -> Bool
$c< :: CompositeDef -> CompositeDef -> Bool
compare :: CompositeDef -> CompositeDef -> Ordering
$ccompare :: CompositeDef -> CompositeDef -> Ordering
Ord, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => CompositeDef -> m Exp
forall (m :: * -> *).
Quote m =>
CompositeDef -> Code m CompositeDef
liftTyped :: forall (m :: * -> *).
Quote m =>
CompositeDef -> Code m CompositeDef
$cliftTyped :: forall (m :: * -> *).
Quote m =>
CompositeDef -> Code m CompositeDef
lift :: forall (m :: * -> *). Quote m => CompositeDef -> m Exp
$clift :: forall (m :: * -> *). Quote m => CompositeDef -> m Exp
Lift)
type ForeignFieldDef = (FieldNameHS, FieldNameDB)
data ForeignDef = ForeignDef
    { ForeignDef -> EntityNameHS
foreignRefTableHaskell       :: !EntityNameHS
    , ForeignDef -> EntityNameDB
foreignRefTableDBName        :: !EntityNameDB
    , ForeignDef -> ConstraintNameHS
foreignConstraintNameHaskell :: !ConstraintNameHS
    , ForeignDef -> ConstraintNameDB
foreignConstraintNameDBName  :: !ConstraintNameDB
    , ForeignDef -> FieldCascade
foreignFieldCascade          :: !FieldCascade
    
    
    
    , ForeignDef
-> [((FieldNameHS, FieldNameDB), (FieldNameHS, FieldNameDB))]
foreignFields                :: ![(ForeignFieldDef, ForeignFieldDef)] 
    , ForeignDef -> [Text]
foreignAttrs                 :: ![Attr]
    , ForeignDef -> Bool
foreignNullable              :: Bool
    , ForeignDef -> Bool
foreignToPrimary             :: Bool
    
    
    
    }
    deriving (Int -> ForeignDef -> ShowS
[ForeignDef] -> ShowS
ForeignDef -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [ForeignDef] -> ShowS
$cshowList :: [ForeignDef] -> ShowS
show :: ForeignDef -> [Char]
$cshow :: ForeignDef -> [Char]
showsPrec :: Int -> ForeignDef -> ShowS
$cshowsPrec :: Int -> ForeignDef -> ShowS
Show, ForeignDef -> ForeignDef -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ForeignDef -> ForeignDef -> Bool
$c/= :: ForeignDef -> ForeignDef -> Bool
== :: ForeignDef -> ForeignDef -> Bool
$c== :: ForeignDef -> ForeignDef -> Bool
Eq, ReadPrec [ForeignDef]
ReadPrec ForeignDef
Int -> ReadS ForeignDef
ReadS [ForeignDef]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ForeignDef]
$creadListPrec :: ReadPrec [ForeignDef]
readPrec :: ReadPrec ForeignDef
$creadPrec :: ReadPrec ForeignDef
readList :: ReadS [ForeignDef]
$creadList :: ReadS [ForeignDef]
readsPrec :: Int -> ReadS ForeignDef
$creadsPrec :: Int -> ReadS ForeignDef
Read, Eq ForeignDef
ForeignDef -> ForeignDef -> Bool
ForeignDef -> ForeignDef -> Ordering
ForeignDef -> ForeignDef -> ForeignDef
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ForeignDef -> ForeignDef -> ForeignDef
$cmin :: ForeignDef -> ForeignDef -> ForeignDef
max :: ForeignDef -> ForeignDef -> ForeignDef
$cmax :: ForeignDef -> ForeignDef -> ForeignDef
>= :: ForeignDef -> ForeignDef -> Bool
$c>= :: ForeignDef -> ForeignDef -> Bool
> :: ForeignDef -> ForeignDef -> Bool
$c> :: ForeignDef -> ForeignDef -> Bool
<= :: ForeignDef -> ForeignDef -> Bool
$c<= :: ForeignDef -> ForeignDef -> Bool
< :: ForeignDef -> ForeignDef -> Bool
$c< :: ForeignDef -> ForeignDef -> Bool
compare :: ForeignDef -> ForeignDef -> Ordering
$ccompare :: ForeignDef -> ForeignDef -> Ordering
Ord, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => ForeignDef -> m Exp
forall (m :: * -> *). Quote m => ForeignDef -> Code m ForeignDef
liftTyped :: forall (m :: * -> *). Quote m => ForeignDef -> Code m ForeignDef
$cliftTyped :: forall (m :: * -> *). Quote m => ForeignDef -> Code m ForeignDef
lift :: forall (m :: * -> *). Quote m => ForeignDef -> m Exp
$clift :: forall (m :: * -> *). Quote m => ForeignDef -> m Exp
Lift)
data FieldCascade = FieldCascade
    { FieldCascade -> Maybe CascadeAction
fcOnUpdate :: !(Maybe CascadeAction)
    , FieldCascade -> Maybe CascadeAction
fcOnDelete :: !(Maybe CascadeAction)
    }
    deriving (Int -> FieldCascade -> ShowS
[FieldCascade] -> ShowS
FieldCascade -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [FieldCascade] -> ShowS
$cshowList :: [FieldCascade] -> ShowS
show :: FieldCascade -> [Char]
$cshow :: FieldCascade -> [Char]
showsPrec :: Int -> FieldCascade -> ShowS
$cshowsPrec :: Int -> FieldCascade -> ShowS
Show, FieldCascade -> FieldCascade -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FieldCascade -> FieldCascade -> Bool
$c/= :: FieldCascade -> FieldCascade -> Bool
== :: FieldCascade -> FieldCascade -> Bool
$c== :: FieldCascade -> FieldCascade -> Bool
Eq, ReadPrec [FieldCascade]
ReadPrec FieldCascade
Int -> ReadS FieldCascade
ReadS [FieldCascade]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FieldCascade]
$creadListPrec :: ReadPrec [FieldCascade]
readPrec :: ReadPrec FieldCascade
$creadPrec :: ReadPrec FieldCascade
readList :: ReadS [FieldCascade]
$creadList :: ReadS [FieldCascade]
readsPrec :: Int -> ReadS FieldCascade
$creadsPrec :: Int -> ReadS FieldCascade
Read, Eq FieldCascade
FieldCascade -> FieldCascade -> Bool
FieldCascade -> FieldCascade -> Ordering
FieldCascade -> FieldCascade -> FieldCascade
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FieldCascade -> FieldCascade -> FieldCascade
$cmin :: FieldCascade -> FieldCascade -> FieldCascade
max :: FieldCascade -> FieldCascade -> FieldCascade
$cmax :: FieldCascade -> FieldCascade -> FieldCascade
>= :: FieldCascade -> FieldCascade -> Bool
$c>= :: FieldCascade -> FieldCascade -> Bool
> :: FieldCascade -> FieldCascade -> Bool
$c> :: FieldCascade -> FieldCascade -> Bool
<= :: FieldCascade -> FieldCascade -> Bool
$c<= :: FieldCascade -> FieldCascade -> Bool
< :: FieldCascade -> FieldCascade -> Bool
$c< :: FieldCascade -> FieldCascade -> Bool
compare :: FieldCascade -> FieldCascade -> Ordering
$ccompare :: FieldCascade -> FieldCascade -> Ordering
Ord, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => FieldCascade -> m Exp
forall (m :: * -> *).
Quote m =>
FieldCascade -> Code m FieldCascade
liftTyped :: forall (m :: * -> *).
Quote m =>
FieldCascade -> Code m FieldCascade
$cliftTyped :: forall (m :: * -> *).
Quote m =>
FieldCascade -> Code m FieldCascade
lift :: forall (m :: * -> *). Quote m => FieldCascade -> m Exp
$clift :: forall (m :: * -> *). Quote m => FieldCascade -> m Exp
Lift)
noCascade :: FieldCascade
noCascade :: FieldCascade
noCascade = Maybe CascadeAction -> Maybe CascadeAction -> FieldCascade
FieldCascade forall a. Maybe a
Nothing forall a. Maybe a
Nothing
renderFieldCascade :: FieldCascade -> Text
renderFieldCascade :: FieldCascade -> Text
renderFieldCascade (FieldCascade Maybe CascadeAction
onUpdate Maybe CascadeAction
onDelete) =
    [Text] -> Text
T.unwords
        [ forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (forall a. Monoid a => a -> a -> a
mappend Text
" ON DELETE " forall b c a. (b -> c) -> (a -> b) -> a -> c
. CascadeAction -> Text
renderCascadeAction) Maybe CascadeAction
onDelete
        , forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (forall a. Monoid a => a -> a -> a
mappend Text
" ON UPDATE " forall b c a. (b -> c) -> (a -> b) -> a -> c
. CascadeAction -> Text
renderCascadeAction) Maybe CascadeAction
onUpdate
        ]
data CascadeAction = Cascade | Restrict | SetNull | SetDefault
    deriving (Int -> CascadeAction -> ShowS
[CascadeAction] -> ShowS
CascadeAction -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [CascadeAction] -> ShowS
$cshowList :: [CascadeAction] -> ShowS
show :: CascadeAction -> [Char]
$cshow :: CascadeAction -> [Char]
showsPrec :: Int -> CascadeAction -> ShowS
$cshowsPrec :: Int -> CascadeAction -> ShowS
Show, CascadeAction -> CascadeAction -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CascadeAction -> CascadeAction -> Bool
$c/= :: CascadeAction -> CascadeAction -> Bool
== :: CascadeAction -> CascadeAction -> Bool
$c== :: CascadeAction -> CascadeAction -> Bool
Eq, ReadPrec [CascadeAction]
ReadPrec CascadeAction
Int -> ReadS CascadeAction
ReadS [CascadeAction]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CascadeAction]
$creadListPrec :: ReadPrec [CascadeAction]
readPrec :: ReadPrec CascadeAction
$creadPrec :: ReadPrec CascadeAction
readList :: ReadS [CascadeAction]
$creadList :: ReadS [CascadeAction]
readsPrec :: Int -> ReadS CascadeAction
$creadsPrec :: Int -> ReadS CascadeAction
Read, Eq CascadeAction
CascadeAction -> CascadeAction -> Bool
CascadeAction -> CascadeAction -> Ordering
CascadeAction -> CascadeAction -> CascadeAction
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CascadeAction -> CascadeAction -> CascadeAction
$cmin :: CascadeAction -> CascadeAction -> CascadeAction
max :: CascadeAction -> CascadeAction -> CascadeAction
$cmax :: CascadeAction -> CascadeAction -> CascadeAction
>= :: CascadeAction -> CascadeAction -> Bool
$c>= :: CascadeAction -> CascadeAction -> Bool
> :: CascadeAction -> CascadeAction -> Bool
$c> :: CascadeAction -> CascadeAction -> Bool
<= :: CascadeAction -> CascadeAction -> Bool
$c<= :: CascadeAction -> CascadeAction -> Bool
< :: CascadeAction -> CascadeAction -> Bool
$c< :: CascadeAction -> CascadeAction -> Bool
compare :: CascadeAction -> CascadeAction -> Ordering
$ccompare :: CascadeAction -> CascadeAction -> Ordering
Ord, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => CascadeAction -> m Exp
forall (m :: * -> *).
Quote m =>
CascadeAction -> Code m CascadeAction
liftTyped :: forall (m :: * -> *).
Quote m =>
CascadeAction -> Code m CascadeAction
$cliftTyped :: forall (m :: * -> *).
Quote m =>
CascadeAction -> Code m CascadeAction
lift :: forall (m :: * -> *). Quote m => CascadeAction -> m Exp
$clift :: forall (m :: * -> *). Quote m => CascadeAction -> m Exp
Lift)
renderCascadeAction :: CascadeAction -> Text
renderCascadeAction :: CascadeAction -> Text
renderCascadeAction CascadeAction
action = case CascadeAction
action of
  CascadeAction
Cascade    -> Text
"CASCADE"
  CascadeAction
Restrict   -> Text
"RESTRICT"
  CascadeAction
SetNull    -> Text
"SET NULL"
  CascadeAction
SetDefault -> Text
"SET DEFAULT"
data PersistException
  = PersistError Text 
  | PersistMarshalError Text
  | PersistInvalidField Text
  | PersistForeignConstraintUnmet Text
  | PersistMongoDBError Text
  | PersistMongoDBUnsupported Text
    deriving Int -> PersistException -> ShowS
[PersistException] -> ShowS
PersistException -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [PersistException] -> ShowS
$cshowList :: [PersistException] -> ShowS
show :: PersistException -> [Char]
$cshow :: PersistException -> [Char]
showsPrec :: Int -> PersistException -> ShowS
$cshowsPrec :: Int -> PersistException -> ShowS
Show
instance Exception PersistException
data SqlType = SqlString
             | SqlInt32
             | SqlInt64
             | SqlReal
             | SqlNumeric Word32 Word32
             | SqlBool
             | SqlDay
             | SqlTime
             | SqlDayTime 
             | SqlBlob
             | SqlOther T.Text 
    deriving (Int -> SqlType -> ShowS
[SqlType] -> ShowS
SqlType -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [SqlType] -> ShowS
$cshowList :: [SqlType] -> ShowS
show :: SqlType -> [Char]
$cshow :: SqlType -> [Char]
showsPrec :: Int -> SqlType -> ShowS
$cshowsPrec :: Int -> SqlType -> ShowS
Show, ReadPrec [SqlType]
ReadPrec SqlType
Int -> ReadS SqlType
ReadS [SqlType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SqlType]
$creadListPrec :: ReadPrec [SqlType]
readPrec :: ReadPrec SqlType
$creadPrec :: ReadPrec SqlType
readList :: ReadS [SqlType]
$creadList :: ReadS [SqlType]
readsPrec :: Int -> ReadS SqlType
$creadsPrec :: Int -> ReadS SqlType
Read, SqlType -> SqlType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SqlType -> SqlType -> Bool
$c/= :: SqlType -> SqlType -> Bool
== :: SqlType -> SqlType -> Bool
$c== :: SqlType -> SqlType -> Bool
Eq, Eq SqlType
SqlType -> SqlType -> Bool
SqlType -> SqlType -> Ordering
SqlType -> SqlType -> SqlType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SqlType -> SqlType -> SqlType
$cmin :: SqlType -> SqlType -> SqlType
max :: SqlType -> SqlType -> SqlType
$cmax :: SqlType -> SqlType -> SqlType
>= :: SqlType -> SqlType -> Bool
$c>= :: SqlType -> SqlType -> Bool
> :: SqlType -> SqlType -> Bool
$c> :: SqlType -> SqlType -> Bool
<= :: SqlType -> SqlType -> Bool
$c<= :: SqlType -> SqlType -> Bool
< :: SqlType -> SqlType -> Bool
$c< :: SqlType -> SqlType -> Bool
compare :: SqlType -> SqlType -> Ordering
$ccompare :: SqlType -> SqlType -> Ordering
Ord, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => SqlType -> m Exp
forall (m :: * -> *). Quote m => SqlType -> Code m SqlType
liftTyped :: forall (m :: * -> *). Quote m => SqlType -> Code m SqlType
$cliftTyped :: forall (m :: * -> *). Quote m => SqlType -> Code m SqlType
lift :: forall (m :: * -> *). Quote m => SqlType -> m Exp
$clift :: forall (m :: * -> *). Quote m => SqlType -> m Exp
Lift)
data PersistFilter = Eq | Ne | Gt | Lt | Ge | Le | In | NotIn
                   | BackendSpecificFilter T.Text
    deriving (ReadPrec [PersistFilter]
ReadPrec PersistFilter
Int -> ReadS PersistFilter
ReadS [PersistFilter]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PersistFilter]
$creadListPrec :: ReadPrec [PersistFilter]
readPrec :: ReadPrec PersistFilter
$creadPrec :: ReadPrec PersistFilter
readList :: ReadS [PersistFilter]
$creadList :: ReadS [PersistFilter]
readsPrec :: Int -> ReadS PersistFilter
$creadsPrec :: Int -> ReadS PersistFilter
Read, Int -> PersistFilter -> ShowS
[PersistFilter] -> ShowS
PersistFilter -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [PersistFilter] -> ShowS
$cshowList :: [PersistFilter] -> ShowS
show :: PersistFilter -> [Char]
$cshow :: PersistFilter -> [Char]
showsPrec :: Int -> PersistFilter -> ShowS
$cshowsPrec :: Int -> PersistFilter -> ShowS
Show, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => PersistFilter -> m Exp
forall (m :: * -> *).
Quote m =>
PersistFilter -> Code m PersistFilter
liftTyped :: forall (m :: * -> *).
Quote m =>
PersistFilter -> Code m PersistFilter
$cliftTyped :: forall (m :: * -> *).
Quote m =>
PersistFilter -> Code m PersistFilter
lift :: forall (m :: * -> *). Quote m => PersistFilter -> m Exp
$clift :: forall (m :: * -> *). Quote m => PersistFilter -> m Exp
Lift)
data UpdateException = KeyNotFound String
                     | UpsertError String
instance Show UpdateException where
    show :: UpdateException -> [Char]
show (KeyNotFound [Char]
key) = [Char]
"Key not found during updateGet: " forall a. [a] -> [a] -> [a]
++ [Char]
key
    show (UpsertError [Char]
msg) = [Char]
"Error during upsert: " forall a. [a] -> [a] -> [a]
++ [Char]
msg
instance Exception UpdateException
data OnlyUniqueException = OnlyUniqueException String
instance Show OnlyUniqueException where
    show :: OnlyUniqueException -> [Char]
show (OnlyUniqueException [Char]
uniqueMsg) =
      [Char]
"Expected only one unique key, got " forall a. [a] -> [a] -> [a]
++ [Char]
uniqueMsg
instance Exception OnlyUniqueException
data PersistUpdate
    = Assign | Add | Subtract | Multiply | Divide
    | BackendSpecificUpdate T.Text
    deriving (ReadPrec [PersistUpdate]
ReadPrec PersistUpdate
Int -> ReadS PersistUpdate
ReadS [PersistUpdate]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PersistUpdate]
$creadListPrec :: ReadPrec [PersistUpdate]
readPrec :: ReadPrec PersistUpdate
$creadPrec :: ReadPrec PersistUpdate
readList :: ReadS [PersistUpdate]
$creadList :: ReadS [PersistUpdate]
readsPrec :: Int -> ReadS PersistUpdate
$creadsPrec :: Int -> ReadS PersistUpdate
Read, Int -> PersistUpdate -> ShowS
[PersistUpdate] -> ShowS
PersistUpdate -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [PersistUpdate] -> ShowS
$cshowList :: [PersistUpdate] -> ShowS
show :: PersistUpdate -> [Char]
$cshow :: PersistUpdate -> [Char]
showsPrec :: Int -> PersistUpdate -> ShowS
$cshowsPrec :: Int -> PersistUpdate -> ShowS
Show, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => PersistUpdate -> m Exp
forall (m :: * -> *).
Quote m =>
PersistUpdate -> Code m PersistUpdate
liftTyped :: forall (m :: * -> *).
Quote m =>
PersistUpdate -> Code m PersistUpdate
$cliftTyped :: forall (m :: * -> *).
Quote m =>
PersistUpdate -> Code m PersistUpdate
lift :: forall (m :: * -> *). Quote m => PersistUpdate -> m Exp
$clift :: forall (m :: * -> *). Quote m => PersistUpdate -> m Exp
Lift)
data FieldDef = FieldDef
    { FieldDef -> FieldNameHS
fieldHaskell   :: !FieldNameHS
    
    
    
    
    
    , FieldDef -> FieldNameDB
fieldDB        :: !FieldNameDB
    
    
    , FieldDef -> FieldType
fieldType      :: !FieldType
    
    , FieldDef -> SqlType
fieldSqlType   :: !SqlType
    
    , FieldDef -> [FieldAttr]
fieldAttrs     :: ![FieldAttr]
    
    
    , FieldDef -> Bool
fieldStrict    :: !Bool
    
    
    , FieldDef -> ReferenceDef
fieldReference :: !ReferenceDef
    , FieldDef -> FieldCascade
fieldCascade :: !FieldCascade
    
    
    
    
    
    
    ,   :: !(Maybe Text)
    
    
    
    , FieldDef -> Maybe Text
fieldGenerated :: !(Maybe Text)
    
    
    
    
    , FieldDef -> Bool
fieldIsImplicitIdColumn :: !Bool
    
    
    
    }
    deriving (Int -> FieldDef -> ShowS
[FieldDef] -> ShowS
FieldDef -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [FieldDef] -> ShowS
$cshowList :: [FieldDef] -> ShowS
show :: FieldDef -> [Char]
$cshow :: FieldDef -> [Char]
showsPrec :: Int -> FieldDef -> ShowS
$cshowsPrec :: Int -> FieldDef -> ShowS
Show, FieldDef -> FieldDef -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FieldDef -> FieldDef -> Bool
$c/= :: FieldDef -> FieldDef -> Bool
== :: FieldDef -> FieldDef -> Bool
$c== :: FieldDef -> FieldDef -> Bool
Eq, ReadPrec [FieldDef]
ReadPrec FieldDef
Int -> ReadS FieldDef
ReadS [FieldDef]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FieldDef]
$creadListPrec :: ReadPrec [FieldDef]
readPrec :: ReadPrec FieldDef
$creadPrec :: ReadPrec FieldDef
readList :: ReadS [FieldDef]
$creadList :: ReadS [FieldDef]
readsPrec :: Int -> ReadS FieldDef
$creadsPrec :: Int -> ReadS FieldDef
Read, Eq FieldDef
FieldDef -> FieldDef -> Bool
FieldDef -> FieldDef -> Ordering
FieldDef -> FieldDef -> FieldDef
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FieldDef -> FieldDef -> FieldDef
$cmin :: FieldDef -> FieldDef -> FieldDef
max :: FieldDef -> FieldDef -> FieldDef
$cmax :: FieldDef -> FieldDef -> FieldDef
>= :: FieldDef -> FieldDef -> Bool
$c>= :: FieldDef -> FieldDef -> Bool
> :: FieldDef -> FieldDef -> Bool
$c> :: FieldDef -> FieldDef -> Bool
<= :: FieldDef -> FieldDef -> Bool
$c<= :: FieldDef -> FieldDef -> Bool
< :: FieldDef -> FieldDef -> Bool
$c< :: FieldDef -> FieldDef -> Bool
compare :: FieldDef -> FieldDef -> Ordering
$ccompare :: FieldDef -> FieldDef -> Ordering
Ord, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => FieldDef -> m Exp
forall (m :: * -> *). Quote m => FieldDef -> Code m FieldDef
liftTyped :: forall (m :: * -> *). Quote m => FieldDef -> Code m FieldDef
$cliftTyped :: forall (m :: * -> *). Quote m => FieldDef -> Code m FieldDef
lift :: forall (m :: * -> *). Quote m => FieldDef -> m Exp
$clift :: forall (m :: * -> *). Quote m => FieldDef -> m Exp
Lift)