{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskell #-}
module Gargantext.Database.Admin.Types.Hyperdata.Contact
where
import Data.Morpheus.Types (GQLType(..))
import Data.Time.Segment (jour)
import qualified Gargantext.API.GraphQL.Utils as GAGU
import Gargantext.Core.Text (HasText(..))
import Gargantext.Database.Admin.Types.Hyperdata.Prelude
import Gargantext.Prelude
import Gargantext.Utils.UTCTime
data HyperdataContact =
HyperdataContact { HyperdataContact -> Maybe Text
_hc_bdd :: Maybe Text
, HyperdataContact -> Maybe ContactWho
_hc_who :: Maybe ContactWho
, HyperdataContact -> [ContactWhere]
_hc_where :: [ContactWhere]
, HyperdataContact -> Maybe Text
_hc_title :: Maybe Text
, HyperdataContact -> Maybe Text
_hc_source :: Maybe Text
, HyperdataContact -> Maybe Text
_hc_lastValidation :: Maybe Text
, HyperdataContact -> Maybe Text
_hc_uniqIdBdd :: Maybe Text
, HyperdataContact -> Maybe Text
_hc_uniqId :: Maybe Text
} deriving (HyperdataContact -> HyperdataContact -> Bool
(HyperdataContact -> HyperdataContact -> Bool)
-> (HyperdataContact -> HyperdataContact -> Bool)
-> Eq HyperdataContact
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HyperdataContact -> HyperdataContact -> Bool
$c/= :: HyperdataContact -> HyperdataContact -> Bool
== :: HyperdataContact -> HyperdataContact -> Bool
$c== :: HyperdataContact -> HyperdataContact -> Bool
Eq, Int -> HyperdataContact -> ShowS
[HyperdataContact] -> ShowS
HyperdataContact -> String
(Int -> HyperdataContact -> ShowS)
-> (HyperdataContact -> String)
-> ([HyperdataContact] -> ShowS)
-> Show HyperdataContact
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HyperdataContact] -> ShowS
$cshowList :: [HyperdataContact] -> ShowS
show :: HyperdataContact -> String
$cshow :: HyperdataContact -> String
showsPrec :: Int -> HyperdataContact -> ShowS
$cshowsPrec :: Int -> HyperdataContact -> ShowS
Show, (forall x. HyperdataContact -> Rep HyperdataContact x)
-> (forall x. Rep HyperdataContact x -> HyperdataContact)
-> Generic HyperdataContact
forall x. Rep HyperdataContact x -> HyperdataContact
forall x. HyperdataContact -> Rep HyperdataContact x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep HyperdataContact x -> HyperdataContact
$cfrom :: forall x. HyperdataContact -> Rep HyperdataContact x
Generic)
instance GQLType HyperdataContact where
typeOptions :: f HyperdataContact -> GQLTypeOptions -> GQLTypeOptions
typeOptions f HyperdataContact
_ = Text -> GQLTypeOptions -> GQLTypeOptions
GAGU.unPrefix Text
"_hc_"
instance HasText HyperdataContact
where
hasText :: HyperdataContact -> [Text]
hasText = HyperdataContact -> [Text]
forall a. HasCallStack => a
undefined
defaultHyperdataContact :: HyperdataContact
defaultHyperdataContact :: HyperdataContact
defaultHyperdataContact =
HyperdataContact :: Maybe Text
-> Maybe ContactWho
-> [ContactWhere]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> HyperdataContact
HyperdataContact
{ _hc_bdd :: Maybe Text
_hc_bdd = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"bdd"
, _hc_who :: Maybe ContactWho
_hc_who = ContactWho -> Maybe ContactWho
forall a. a -> Maybe a
Just ContactWho
defaultContactWho
, _hc_where :: [ContactWhere]
_hc_where = [ContactWhere
defaultContactWhere]
, _hc_title :: Maybe Text
_hc_title =Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"Title"
, _hc_source :: Maybe Text
_hc_source = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"Source"
, _hc_lastValidation :: Maybe Text
_hc_lastValidation = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"TODO lastValidation date"
, _hc_uniqIdBdd :: Maybe Text
_hc_uniqIdBdd = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"DO NOT expose this"
, _hc_uniqId :: Maybe Text
_hc_uniqId = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"DO NOT expose this" }
hyperdataContact :: FirstName -> LastName -> HyperdataContact
hyperdataContact :: Text -> Text -> HyperdataContact
hyperdataContact Text
fn Text
ln =
HyperdataContact :: Maybe Text
-> Maybe ContactWho
-> [ContactWhere]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> HyperdataContact
HyperdataContact
{ _hc_bdd :: Maybe Text
_hc_bdd = Maybe Text
forall a. Maybe a
Nothing
, _hc_who :: Maybe ContactWho
_hc_who = ContactWho -> Maybe ContactWho
forall a. a -> Maybe a
Just (Text -> Text -> ContactWho
contactWho Text
fn Text
ln)
, _hc_where :: [ContactWhere]
_hc_where = []
, _hc_title :: Maybe Text
_hc_title = Maybe Text
forall a. Maybe a
Nothing
, _hc_source :: Maybe Text
_hc_source = Maybe Text
forall a. Maybe a
Nothing
, _hc_lastValidation :: Maybe Text
_hc_lastValidation = Maybe Text
forall a. Maybe a
Nothing
, _hc_uniqIdBdd :: Maybe Text
_hc_uniqIdBdd = Maybe Text
forall a. Maybe a
Nothing
, _hc_uniqId :: Maybe Text
_hc_uniqId = Maybe Text
forall a. Maybe a
Nothing }
data ContactMetaData =
ContactMetaData { ContactMetaData -> Maybe Text
_cm_bdd :: Maybe Text
, ContactMetaData -> Maybe Text
_cm_lastValidation :: Maybe Text
} deriving (ContactMetaData -> ContactMetaData -> Bool
(ContactMetaData -> ContactMetaData -> Bool)
-> (ContactMetaData -> ContactMetaData -> Bool)
-> Eq ContactMetaData
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ContactMetaData -> ContactMetaData -> Bool
$c/= :: ContactMetaData -> ContactMetaData -> Bool
== :: ContactMetaData -> ContactMetaData -> Bool
$c== :: ContactMetaData -> ContactMetaData -> Bool
Eq, Int -> ContactMetaData -> ShowS
[ContactMetaData] -> ShowS
ContactMetaData -> String
(Int -> ContactMetaData -> ShowS)
-> (ContactMetaData -> String)
-> ([ContactMetaData] -> ShowS)
-> Show ContactMetaData
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ContactMetaData] -> ShowS
$cshowList :: [ContactMetaData] -> ShowS
show :: ContactMetaData -> String
$cshow :: ContactMetaData -> String
showsPrec :: Int -> ContactMetaData -> ShowS
$cshowsPrec :: Int -> ContactMetaData -> ShowS
Show, (forall x. ContactMetaData -> Rep ContactMetaData x)
-> (forall x. Rep ContactMetaData x -> ContactMetaData)
-> Generic ContactMetaData
forall x. Rep ContactMetaData x -> ContactMetaData
forall x. ContactMetaData -> Rep ContactMetaData x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ContactMetaData x -> ContactMetaData
$cfrom :: forall x. ContactMetaData -> Rep ContactMetaData x
Generic)
defaultContactMetaData :: ContactMetaData
defaultContactMetaData :: ContactMetaData
defaultContactMetaData = Maybe Text -> Maybe Text -> ContactMetaData
ContactMetaData (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"bdd") (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"TODO UTCTime")
arbitraryHyperdataContact :: HyperdataContact
arbitraryHyperdataContact :: HyperdataContact
arbitraryHyperdataContact =
HyperdataContact :: Maybe Text
-> Maybe ContactWho
-> [ContactWhere]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> HyperdataContact
HyperdataContact
{ _hc_bdd :: Maybe Text
_hc_bdd = Maybe Text
forall a. Maybe a
Nothing
, _hc_who :: Maybe ContactWho
_hc_who = Maybe ContactWho
forall a. Maybe a
Nothing
, _hc_where :: [ContactWhere]
_hc_where = []
, _hc_title :: Maybe Text
_hc_title = Maybe Text
forall a. Maybe a
Nothing
, _hc_source :: Maybe Text
_hc_source = Maybe Text
forall a. Maybe a
Nothing
, _hc_lastValidation :: Maybe Text
_hc_lastValidation = Maybe Text
forall a. Maybe a
Nothing
, _hc_uniqIdBdd :: Maybe Text
_hc_uniqIdBdd = Maybe Text
forall a. Maybe a
Nothing
, _hc_uniqId :: Maybe Text
_hc_uniqId = Maybe Text
forall a. Maybe a
Nothing }
data ContactWho =
ContactWho { ContactWho -> Maybe Text
_cw_id :: Maybe Text
, ContactWho -> Maybe Text
_cw_firstName :: Maybe Text
, ContactWho -> Maybe Text
_cw_lastName :: Maybe Text
, ContactWho -> [Text]
_cw_keywords :: [Text]
, ContactWho -> [Text]
_cw_freetags :: [Text]
} deriving (ContactWho -> ContactWho -> Bool
(ContactWho -> ContactWho -> Bool)
-> (ContactWho -> ContactWho -> Bool) -> Eq ContactWho
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ContactWho -> ContactWho -> Bool
$c/= :: ContactWho -> ContactWho -> Bool
== :: ContactWho -> ContactWho -> Bool
$c== :: ContactWho -> ContactWho -> Bool
Eq, Int -> ContactWho -> ShowS
[ContactWho] -> ShowS
ContactWho -> String
(Int -> ContactWho -> ShowS)
-> (ContactWho -> String)
-> ([ContactWho] -> ShowS)
-> Show ContactWho
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ContactWho] -> ShowS
$cshowList :: [ContactWho] -> ShowS
show :: ContactWho -> String
$cshow :: ContactWho -> String
showsPrec :: Int -> ContactWho -> ShowS
$cshowsPrec :: Int -> ContactWho -> ShowS
Show, (forall x. ContactWho -> Rep ContactWho x)
-> (forall x. Rep ContactWho x -> ContactWho) -> Generic ContactWho
forall x. Rep ContactWho x -> ContactWho
forall x. ContactWho -> Rep ContactWho x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ContactWho x -> ContactWho
$cfrom :: forall x. ContactWho -> Rep ContactWho x
Generic)
instance GQLType ContactWho where
typeOptions :: f ContactWho -> GQLTypeOptions -> GQLTypeOptions
typeOptions f ContactWho
_ = Text -> GQLTypeOptions -> GQLTypeOptions
GAGU.unPrefix Text
"_cw_"
type FirstName = Text
type LastName = Text
defaultContactWho :: ContactWho
defaultContactWho :: ContactWho
defaultContactWho = Text -> Text -> ContactWho
contactWho Text
"Pierre" Text
"Dupont"
contactWho :: FirstName -> LastName -> ContactWho
contactWho :: Text -> Text -> ContactWho
contactWho Text
fn Text
ln =
ContactWho :: Maybe Text
-> Maybe Text -> Maybe Text -> [Text] -> [Text] -> ContactWho
ContactWho { _cw_id :: Maybe Text
_cw_id = Maybe Text
forall a. Maybe a
Nothing
, _cw_firstName :: Maybe Text
_cw_firstName = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
fn
, _cw_lastName :: Maybe Text
_cw_lastName = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
ln
, _cw_keywords :: [Text]
_cw_keywords = []
, _cw_freetags :: [Text]
_cw_freetags = [] }
data ContactWhere =
ContactWhere { ContactWhere -> [Text]
_cw_organization :: [Text]
, ContactWhere -> [Text]
_cw_labTeamDepts :: [Text]
, ContactWhere -> Maybe Text
_cw_role :: Maybe Text
, ContactWhere -> Maybe Text
_cw_office :: Maybe Text
, ContactWhere -> Maybe Text
_cw_country :: Maybe Text
, ContactWhere -> Maybe Text
_cw_city :: Maybe Text
, ContactWhere -> Maybe ContactTouch
_cw_touch :: Maybe ContactTouch
, ContactWhere -> Maybe NUTCTime
_cw_entry :: Maybe NUTCTime
, ContactWhere -> Maybe NUTCTime
_cw_exit :: Maybe NUTCTime
} deriving (ContactWhere -> ContactWhere -> Bool
(ContactWhere -> ContactWhere -> Bool)
-> (ContactWhere -> ContactWhere -> Bool) -> Eq ContactWhere
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ContactWhere -> ContactWhere -> Bool
$c/= :: ContactWhere -> ContactWhere -> Bool
== :: ContactWhere -> ContactWhere -> Bool
$c== :: ContactWhere -> ContactWhere -> Bool
Eq, Int -> ContactWhere -> ShowS
[ContactWhere] -> ShowS
ContactWhere -> String
(Int -> ContactWhere -> ShowS)
-> (ContactWhere -> String)
-> ([ContactWhere] -> ShowS)
-> Show ContactWhere
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ContactWhere] -> ShowS
$cshowList :: [ContactWhere] -> ShowS
show :: ContactWhere -> String
$cshow :: ContactWhere -> String
showsPrec :: Int -> ContactWhere -> ShowS
$cshowsPrec :: Int -> ContactWhere -> ShowS
Show, (forall x. ContactWhere -> Rep ContactWhere x)
-> (forall x. Rep ContactWhere x -> ContactWhere)
-> Generic ContactWhere
forall x. Rep ContactWhere x -> ContactWhere
forall x. ContactWhere -> Rep ContactWhere x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ContactWhere x -> ContactWhere
$cfrom :: forall x. ContactWhere -> Rep ContactWhere x
Generic)
instance GQLType ContactWhere where
typeOptions :: f ContactWhere -> GQLTypeOptions -> GQLTypeOptions
typeOptions f ContactWhere
_ = Text -> GQLTypeOptions -> GQLTypeOptions
GAGU.unPrefix Text
"_cw_"
defaultContactWhere :: ContactWhere
defaultContactWhere :: ContactWhere
defaultContactWhere =
ContactWhere :: [Text]
-> [Text]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe ContactTouch
-> Maybe NUTCTime
-> Maybe NUTCTime
-> ContactWhere
ContactWhere
{ _cw_organization :: [Text]
_cw_organization = [Text
"Organization X"]
, _cw_labTeamDepts :: [Text]
_cw_labTeamDepts = [Text
"Lab Z"]
, _cw_role :: Maybe Text
_cw_role = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"Role"
, _cw_office :: Maybe Text
_cw_office = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"Office"
, _cw_country :: Maybe Text
_cw_country = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"Country"
, _cw_city :: Maybe Text
_cw_city = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"City"
, _cw_touch :: Maybe ContactTouch
_cw_touch = ContactTouch -> Maybe ContactTouch
forall a. a -> Maybe a
Just ContactTouch
defaultContactTouch
, _cw_entry :: Maybe NUTCTime
_cw_entry = NUTCTime -> Maybe NUTCTime
forall a. a -> Maybe a
Just (NUTCTime -> Maybe NUTCTime) -> NUTCTime -> Maybe NUTCTime
forall a b. (a -> b) -> a -> b
$ UTCTime -> NUTCTime
NUTCTime (UTCTime -> NUTCTime) -> UTCTime -> NUTCTime
forall a b. (a -> b) -> a -> b
$ Integer -> Int -> Int -> UTCTime
jour Integer
01 Int
01 Int
2020
, _cw_exit :: Maybe NUTCTime
_cw_exit = NUTCTime -> Maybe NUTCTime
forall a. a -> Maybe a
Just (NUTCTime -> Maybe NUTCTime) -> NUTCTime -> Maybe NUTCTime
forall a b. (a -> b) -> a -> b
$ UTCTime -> NUTCTime
NUTCTime (UTCTime -> NUTCTime) -> UTCTime -> NUTCTime
forall a b. (a -> b) -> a -> b
$ Integer -> Int -> Int -> UTCTime
jour Integer
01 Int
01 Int
2029 }
data ContactTouch =
ContactTouch { ContactTouch -> Maybe Text
_ct_mail :: Maybe Text
, ContactTouch -> Maybe Text
_ct_phone :: Maybe Text
, ContactTouch -> Maybe Text
_ct_url :: Maybe Text
} deriving (ContactTouch -> ContactTouch -> Bool
(ContactTouch -> ContactTouch -> Bool)
-> (ContactTouch -> ContactTouch -> Bool) -> Eq ContactTouch
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ContactTouch -> ContactTouch -> Bool
$c/= :: ContactTouch -> ContactTouch -> Bool
== :: ContactTouch -> ContactTouch -> Bool
$c== :: ContactTouch -> ContactTouch -> Bool
Eq, Int -> ContactTouch -> ShowS
[ContactTouch] -> ShowS
ContactTouch -> String
(Int -> ContactTouch -> ShowS)
-> (ContactTouch -> String)
-> ([ContactTouch] -> ShowS)
-> Show ContactTouch
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ContactTouch] -> ShowS
$cshowList :: [ContactTouch] -> ShowS
show :: ContactTouch -> String
$cshow :: ContactTouch -> String
showsPrec :: Int -> ContactTouch -> ShowS
$cshowsPrec :: Int -> ContactTouch -> ShowS
Show, (forall x. ContactTouch -> Rep ContactTouch x)
-> (forall x. Rep ContactTouch x -> ContactTouch)
-> Generic ContactTouch
forall x. Rep ContactTouch x -> ContactTouch
forall x. ContactTouch -> Rep ContactTouch x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ContactTouch x -> ContactTouch
$cfrom :: forall x. ContactTouch -> Rep ContactTouch x
Generic)
instance GQLType ContactTouch where
typeOptions :: f ContactTouch -> GQLTypeOptions -> GQLTypeOptions
typeOptions f ContactTouch
_ = Text -> GQLTypeOptions -> GQLTypeOptions
GAGU.unPrefix Text
"_ct_"
defaultContactTouch :: ContactTouch
defaultContactTouch :: ContactTouch
defaultContactTouch =
ContactTouch :: Maybe Text -> Maybe Text -> Maybe Text -> ContactTouch
ContactTouch
{ _ct_mail :: Maybe Text
_ct_mail = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"email@data.com"
, _ct_phone :: Maybe Text
_ct_phone = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"+336 328 283 288"
, _ct_url :: Maybe Text
_ct_url = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"https://url.com" }
instance ToSchema HyperdataContact where
declareNamedSchema :: Proxy HyperdataContact -> Declare (Definitions Schema) NamedSchema
declareNamedSchema = SchemaOptions
-> Proxy HyperdataContact
-> Declare (Definitions Schema) NamedSchema
forall a.
(Generic a, GToSchema (Rep a),
TypeHasSimpleShape a "genericDeclareNamedSchemaUnrestricted") =>
SchemaOptions
-> Proxy a -> Declare (Definitions Schema) NamedSchema
genericDeclareNamedSchema (String -> SchemaOptions
unPrefixSwagger String
"_hc_")
instance ToSchema ContactWho where
declareNamedSchema :: Proxy ContactWho -> Declare (Definitions Schema) NamedSchema
declareNamedSchema = SchemaOptions
-> Proxy ContactWho -> Declare (Definitions Schema) NamedSchema
forall a.
(Generic a, GToSchema (Rep a),
TypeHasSimpleShape a "genericDeclareNamedSchemaUnrestricted") =>
SchemaOptions
-> Proxy a -> Declare (Definitions Schema) NamedSchema
genericDeclareNamedSchema (String -> SchemaOptions
unPrefixSwagger String
"_cw_")
instance ToSchema ContactWhere where
declareNamedSchema :: Proxy ContactWhere -> Declare (Definitions Schema) NamedSchema
declareNamedSchema = SchemaOptions
-> Proxy ContactWhere -> Declare (Definitions Schema) NamedSchema
forall a.
(Generic a, GToSchema (Rep a),
TypeHasSimpleShape a "genericDeclareNamedSchemaUnrestricted") =>
SchemaOptions
-> Proxy a -> Declare (Definitions Schema) NamedSchema
genericDeclareNamedSchema (String -> SchemaOptions
unPrefixSwagger String
"_cw_")
instance ToSchema ContactTouch where
declareNamedSchema :: Proxy ContactTouch -> Declare (Definitions Schema) NamedSchema
declareNamedSchema = SchemaOptions
-> Proxy ContactTouch -> Declare (Definitions Schema) NamedSchema
forall a.
(Generic a, GToSchema (Rep a),
TypeHasSimpleShape a "genericDeclareNamedSchemaUnrestricted") =>
SchemaOptions
-> Proxy a -> Declare (Definitions Schema) NamedSchema
genericDeclareNamedSchema (String -> SchemaOptions
unPrefixSwagger String
"_ct_")
instance ToSchema ContactMetaData where
declareNamedSchema :: Proxy ContactMetaData -> Declare (Definitions Schema) NamedSchema
declareNamedSchema = SchemaOptions
-> Proxy ContactMetaData
-> Declare (Definitions Schema) NamedSchema
forall a.
(Generic a, GToSchema (Rep a),
TypeHasSimpleShape a "genericDeclareNamedSchemaUnrestricted") =>
SchemaOptions
-> Proxy a -> Declare (Definitions Schema) NamedSchema
genericDeclareNamedSchema (String -> SchemaOptions
unPrefixSwagger String
"_cm_")
instance Arbitrary HyperdataContact where
arbitrary :: Gen HyperdataContact
arbitrary = [HyperdataContact] -> Gen HyperdataContact
forall a. [a] -> Gen a
elements [Maybe Text
-> Maybe ContactWho
-> [ContactWhere]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> HyperdataContact
HyperdataContact Maybe Text
forall a. Maybe a
Nothing Maybe ContactWho
forall a. Maybe a
Nothing [] Maybe Text
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing]
instance Hyperdata HyperdataContact
instance FromField HyperdataContact where
fromField :: FieldParser HyperdataContact
fromField = FieldParser HyperdataContact
forall b.
(Typeable b, FromJSON b) =>
Field -> Maybe ByteString -> Conversion b
fromField'
instance DefaultFromField PGJsonb HyperdataContact where
defaultFromField :: FromField PGJsonb HyperdataContact
defaultFromField = FromField PGJsonb HyperdataContact
forall haskell pgType.
FromField haskell =>
FromField pgType haskell
fieldQueryRunnerColumn
instance DefaultFromField (Nullable PGJsonb) HyperdataContact where
defaultFromField :: FromField (Nullable PGJsonb) HyperdataContact
defaultFromField = FromField (Nullable PGJsonb) HyperdataContact
forall haskell pgType.
FromField haskell =>
FromField pgType haskell
fieldQueryRunnerColumn
makeLenses ''ContactWho
makeLenses ''ContactWhere
makeLenses ''ContactTouch
makeLenses ''ContactMetaData
makeLenses ''HyperdataContact
$(deriveJSON (unPrefix "_cw_") ''ContactWho)
$(deriveJSON (unPrefix "_cw_") ''ContactWhere)
$(deriveJSON (unPrefix "_ct_") ''ContactTouch)
$(deriveJSON (unPrefix "_cm_") ''ContactMetaData)
$(deriveJSON (unPrefix "_hc_") ''HyperdataContact)