module Hasura.Backends.DataConnector.IR.Relationships ( RelationshipName, mkRelationshipName, TableRelationships (..), Relationship (..), RelationshipType (..), SourceColumnName, TargetColumnName, ) where import Data.Aeson (ToJSON (..)) import Data.Aeson qualified as J import Data.HashMap.Strict qualified as HashMap import Data.Text.Extended (toTxt) import Hasura.Backends.DataConnector.API qualified as API import Hasura.Backends.DataConnector.IR.Column qualified as IR.C import Hasura.Backends.DataConnector.IR.Name qualified as IR.N import Hasura.Backends.DataConnector.IR.Table qualified as IR.T import Hasura.Prelude import Hasura.RQL.Types.Common (RelName (..)) import Witch qualified type RelationshipName = IR.N.Name 'IR.N.Relationship mkRelationshipName :: RelName -> RelationshipName mkRelationshipName :: RelName -> RelationshipName mkRelationshipName RelName relName = Text -> RelationshipName forall (ty :: NameType). Text -> Name ty IR.N.Name @('IR.N.Relationship) (Text -> RelationshipName) -> Text -> RelationshipName forall a b. (a -> b) -> a -> b $ RelName -> Text forall a. ToTxt a => a -> Text toTxt RelName relName type SourceTableName = IR.T.Name newtype TableRelationships = TableRelationships {TableRelationships -> HashMap SourceTableName (HashMap RelationshipName Relationship) unTableRelationships :: HashMap SourceTableName (HashMap RelationshipName Relationship)} deriving stock (TableRelationships -> TableRelationships -> Bool (TableRelationships -> TableRelationships -> Bool) -> (TableRelationships -> TableRelationships -> Bool) -> Eq TableRelationships forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: TableRelationships -> TableRelationships -> Bool $c/= :: TableRelationships -> TableRelationships -> Bool == :: TableRelationships -> TableRelationships -> Bool $c== :: TableRelationships -> TableRelationships -> Bool Eq, Eq TableRelationships Eq TableRelationships -> (TableRelationships -> TableRelationships -> Ordering) -> (TableRelationships -> TableRelationships -> Bool) -> (TableRelationships -> TableRelationships -> Bool) -> (TableRelationships -> TableRelationships -> Bool) -> (TableRelationships -> TableRelationships -> Bool) -> (TableRelationships -> TableRelationships -> TableRelationships) -> (TableRelationships -> TableRelationships -> TableRelationships) -> Ord TableRelationships TableRelationships -> TableRelationships -> Bool TableRelationships -> TableRelationships -> Ordering TableRelationships -> TableRelationships -> TableRelationships 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 :: TableRelationships -> TableRelationships -> TableRelationships $cmin :: TableRelationships -> TableRelationships -> TableRelationships max :: TableRelationships -> TableRelationships -> TableRelationships $cmax :: TableRelationships -> TableRelationships -> TableRelationships >= :: TableRelationships -> TableRelationships -> Bool $c>= :: TableRelationships -> TableRelationships -> Bool > :: TableRelationships -> TableRelationships -> Bool $c> :: TableRelationships -> TableRelationships -> Bool <= :: TableRelationships -> TableRelationships -> Bool $c<= :: TableRelationships -> TableRelationships -> Bool < :: TableRelationships -> TableRelationships -> Bool $c< :: TableRelationships -> TableRelationships -> Bool compare :: TableRelationships -> TableRelationships -> Ordering $ccompare :: TableRelationships -> TableRelationships -> Ordering $cp1Ord :: Eq TableRelationships Ord, Int -> TableRelationships -> ShowS [TableRelationships] -> ShowS TableRelationships -> String (Int -> TableRelationships -> ShowS) -> (TableRelationships -> String) -> ([TableRelationships] -> ShowS) -> Show TableRelationships forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [TableRelationships] -> ShowS $cshowList :: [TableRelationships] -> ShowS show :: TableRelationships -> String $cshow :: TableRelationships -> String showsPrec :: Int -> TableRelationships -> ShowS $cshowsPrec :: Int -> TableRelationships -> ShowS Show, Typeable TableRelationships DataType Constr Typeable TableRelationships -> (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TableRelationships -> c TableRelationships) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TableRelationships) -> (TableRelationships -> Constr) -> (TableRelationships -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TableRelationships)) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableRelationships)) -> ((forall b. Data b => b -> b) -> TableRelationships -> TableRelationships) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TableRelationships -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TableRelationships -> r) -> (forall u. (forall d. Data d => d -> u) -> TableRelationships -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> TableRelationships -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> TableRelationships -> m TableRelationships) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> TableRelationships -> m TableRelationships) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> TableRelationships -> m TableRelationships) -> Data TableRelationships TableRelationships -> DataType TableRelationships -> Constr (forall b. Data b => b -> b) -> TableRelationships -> TableRelationships (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TableRelationships -> c TableRelationships (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TableRelationships forall a. Typeable a -> (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> a -> c a) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a) -> (a -> Constr) -> (a -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c a)) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a)) -> ((forall b. Data b => b -> b) -> a -> a) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall u. (forall d. Data d => d -> u) -> a -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> Data a forall u. Int -> (forall d. Data d => d -> u) -> TableRelationships -> u forall u. (forall d. Data d => d -> u) -> TableRelationships -> [u] forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TableRelationships -> r forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TableRelationships -> r forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> TableRelationships -> m TableRelationships forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> TableRelationships -> m TableRelationships forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TableRelationships forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TableRelationships -> c TableRelationships forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TableRelationships) forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableRelationships) $cTableRelationships :: Constr $tTableRelationships :: DataType gmapMo :: (forall d. Data d => d -> m d) -> TableRelationships -> m TableRelationships $cgmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> TableRelationships -> m TableRelationships gmapMp :: (forall d. Data d => d -> m d) -> TableRelationships -> m TableRelationships $cgmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> TableRelationships -> m TableRelationships gmapM :: (forall d. Data d => d -> m d) -> TableRelationships -> m TableRelationships $cgmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> TableRelationships -> m TableRelationships gmapQi :: Int -> (forall d. Data d => d -> u) -> TableRelationships -> u $cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TableRelationships -> u gmapQ :: (forall d. Data d => d -> u) -> TableRelationships -> [u] $cgmapQ :: forall u. (forall d. Data d => d -> u) -> TableRelationships -> [u] gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TableRelationships -> r $cgmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TableRelationships -> r gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TableRelationships -> r $cgmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TableRelationships -> r gmapT :: (forall b. Data b => b -> b) -> TableRelationships -> TableRelationships $cgmapT :: (forall b. Data b => b -> b) -> TableRelationships -> TableRelationships dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableRelationships) $cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableRelationships) dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c TableRelationships) $cdataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TableRelationships) dataTypeOf :: TableRelationships -> DataType $cdataTypeOf :: TableRelationships -> DataType toConstr :: TableRelationships -> Constr $ctoConstr :: TableRelationships -> Constr gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TableRelationships $cgunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TableRelationships gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TableRelationships -> c TableRelationships $cgfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TableRelationships -> c TableRelationships $cp1Data :: Typeable TableRelationships Data, (forall x. TableRelationships -> Rep TableRelationships x) -> (forall x. Rep TableRelationships x -> TableRelationships) -> Generic TableRelationships forall x. Rep TableRelationships x -> TableRelationships forall x. TableRelationships -> Rep TableRelationships x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep TableRelationships x -> TableRelationships $cfrom :: forall x. TableRelationships -> Rep TableRelationships x Generic) deriving newtype ([TableRelationships] -> Value [TableRelationships] -> Encoding TableRelationships -> Value TableRelationships -> Encoding (TableRelationships -> Value) -> (TableRelationships -> Encoding) -> ([TableRelationships] -> Value) -> ([TableRelationships] -> Encoding) -> ToJSON TableRelationships forall a. (a -> Value) -> (a -> Encoding) -> ([a] -> Value) -> ([a] -> Encoding) -> ToJSON a toEncodingList :: [TableRelationships] -> Encoding $ctoEncodingList :: [TableRelationships] -> Encoding toJSONList :: [TableRelationships] -> Value $ctoJSONList :: [TableRelationships] -> Value toEncoding :: TableRelationships -> Encoding $ctoEncoding :: TableRelationships -> Encoding toJSON :: TableRelationships -> Value $ctoJSON :: TableRelationships -> Value ToJSON) instance Semigroup TableRelationships where (TableRelationships HashMap SourceTableName (HashMap RelationshipName Relationship) l) <> :: TableRelationships -> TableRelationships -> TableRelationships <> (TableRelationships HashMap SourceTableName (HashMap RelationshipName Relationship) r) = HashMap SourceTableName (HashMap RelationshipName Relationship) -> TableRelationships TableRelationships (HashMap SourceTableName (HashMap RelationshipName Relationship) -> TableRelationships) -> HashMap SourceTableName (HashMap RelationshipName Relationship) -> TableRelationships forall a b. (a -> b) -> a -> b $ (HashMap RelationshipName Relationship -> HashMap RelationshipName Relationship -> HashMap RelationshipName Relationship) -> HashMap SourceTableName (HashMap RelationshipName Relationship) -> HashMap SourceTableName (HashMap RelationshipName Relationship) -> HashMap SourceTableName (HashMap RelationshipName Relationship) forall k v. (Eq k, Hashable k) => (v -> v -> v) -> HashMap k v -> HashMap k v -> HashMap k v HashMap.unionWith HashMap RelationshipName Relationship -> HashMap RelationshipName Relationship -> HashMap RelationshipName Relationship forall k v. (Eq k, Hashable k) => HashMap k v -> HashMap k v -> HashMap k v HashMap.union HashMap SourceTableName (HashMap RelationshipName Relationship) l HashMap SourceTableName (HashMap RelationshipName Relationship) r instance Monoid TableRelationships where mempty :: TableRelationships mempty = HashMap SourceTableName (HashMap RelationshipName Relationship) -> TableRelationships TableRelationships HashMap SourceTableName (HashMap RelationshipName Relationship) forall a. Monoid a => a mempty data Relationship = Relationship { Relationship -> SourceTableName _rTargetTable :: IR.T.Name, Relationship -> RelationshipType _rRelationshipType :: RelationshipType, Relationship -> HashMap SourceColumnName SourceColumnName _rColumnMapping :: HashMap SourceColumnName TargetColumnName } deriving stock (Typeable Relationship DataType Constr Typeable Relationship -> (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Relationship -> c Relationship) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Relationship) -> (Relationship -> Constr) -> (Relationship -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Relationship)) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Relationship)) -> ((forall b. Data b => b -> b) -> Relationship -> Relationship) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Relationship -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Relationship -> r) -> (forall u. (forall d. Data d => d -> u) -> Relationship -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> Relationship -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Relationship -> m Relationship) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Relationship -> m Relationship) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Relationship -> m Relationship) -> Data Relationship Relationship -> DataType Relationship -> Constr (forall b. Data b => b -> b) -> Relationship -> Relationship (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Relationship -> c Relationship (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Relationship forall a. Typeable a -> (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> a -> c a) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a) -> (a -> Constr) -> (a -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c a)) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a)) -> ((forall b. Data b => b -> b) -> a -> a) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall u. (forall d. Data d => d -> u) -> a -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> Data a forall u. Int -> (forall d. Data d => d -> u) -> Relationship -> u forall u. (forall d. Data d => d -> u) -> Relationship -> [u] forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Relationship -> r forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Relationship -> r forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Relationship -> m Relationship forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Relationship -> m Relationship forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Relationship forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Relationship -> c Relationship forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Relationship) forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Relationship) $cRelationship :: Constr $tRelationship :: DataType gmapMo :: (forall d. Data d => d -> m d) -> Relationship -> m Relationship $cgmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Relationship -> m Relationship gmapMp :: (forall d. Data d => d -> m d) -> Relationship -> m Relationship $cgmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> Relationship -> m Relationship gmapM :: (forall d. Data d => d -> m d) -> Relationship -> m Relationship $cgmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> Relationship -> m Relationship gmapQi :: Int -> (forall d. Data d => d -> u) -> Relationship -> u $cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Relationship -> u gmapQ :: (forall d. Data d => d -> u) -> Relationship -> [u] $cgmapQ :: forall u. (forall d. Data d => d -> u) -> Relationship -> [u] gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Relationship -> r $cgmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Relationship -> r gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Relationship -> r $cgmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Relationship -> r gmapT :: (forall b. Data b => b -> b) -> Relationship -> Relationship $cgmapT :: (forall b. Data b => b -> b) -> Relationship -> Relationship dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Relationship) $cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Relationship) dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Relationship) $cdataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Relationship) dataTypeOf :: Relationship -> DataType $cdataTypeOf :: Relationship -> DataType toConstr :: Relationship -> Constr $ctoConstr :: Relationship -> Constr gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Relationship $cgunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Relationship gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Relationship -> c Relationship $cgfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Relationship -> c Relationship $cp1Data :: Typeable Relationship Data, Relationship -> Relationship -> Bool (Relationship -> Relationship -> Bool) -> (Relationship -> Relationship -> Bool) -> Eq Relationship forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Relationship -> Relationship -> Bool $c/= :: Relationship -> Relationship -> Bool == :: Relationship -> Relationship -> Bool $c== :: Relationship -> Relationship -> Bool Eq, (forall x. Relationship -> Rep Relationship x) -> (forall x. Rep Relationship x -> Relationship) -> Generic Relationship forall x. Rep Relationship x -> Relationship forall x. Relationship -> Rep Relationship x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep Relationship x -> Relationship $cfrom :: forall x. Relationship -> Rep Relationship x Generic, Eq Relationship Eq Relationship -> (Relationship -> Relationship -> Ordering) -> (Relationship -> Relationship -> Bool) -> (Relationship -> Relationship -> Bool) -> (Relationship -> Relationship -> Bool) -> (Relationship -> Relationship -> Bool) -> (Relationship -> Relationship -> Relationship) -> (Relationship -> Relationship -> Relationship) -> Ord Relationship Relationship -> Relationship -> Bool Relationship -> Relationship -> Ordering Relationship -> Relationship -> Relationship 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 :: Relationship -> Relationship -> Relationship $cmin :: Relationship -> Relationship -> Relationship max :: Relationship -> Relationship -> Relationship $cmax :: Relationship -> Relationship -> Relationship >= :: Relationship -> Relationship -> Bool $c>= :: Relationship -> Relationship -> Bool > :: Relationship -> Relationship -> Bool $c> :: Relationship -> Relationship -> Bool <= :: Relationship -> Relationship -> Bool $c<= :: Relationship -> Relationship -> Bool < :: Relationship -> Relationship -> Bool $c< :: Relationship -> Relationship -> Bool compare :: Relationship -> Relationship -> Ordering $ccompare :: Relationship -> Relationship -> Ordering $cp1Ord :: Eq Relationship Ord, Int -> Relationship -> ShowS [Relationship] -> ShowS Relationship -> String (Int -> Relationship -> ShowS) -> (Relationship -> String) -> ([Relationship] -> ShowS) -> Show Relationship forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Relationship] -> ShowS $cshowList :: [Relationship] -> ShowS show :: Relationship -> String $cshow :: Relationship -> String showsPrec :: Int -> Relationship -> ShowS $cshowsPrec :: Int -> Relationship -> ShowS Show) instance ToJSON Relationship where toJSON :: Relationship -> Value toJSON = Options -> Relationship -> Value forall a. (Generic a, GToJSON' Value Zero (Rep a)) => Options -> a -> Value J.genericToJSON Options J.defaultOptions instance Witch.From Relationship API.Relationship where from :: Relationship -> Relationship from Relationship {HashMap SourceColumnName SourceColumnName SourceTableName RelationshipType _rColumnMapping :: HashMap SourceColumnName SourceColumnName _rRelationshipType :: RelationshipType _rTargetTable :: SourceTableName _rColumnMapping :: Relationship -> HashMap SourceColumnName SourceColumnName _rRelationshipType :: Relationship -> RelationshipType _rTargetTable :: Relationship -> SourceTableName ..} = Relationship :: TableName -> RelationshipType -> HashMap SourceColumnName SourceColumnName -> Relationship API.Relationship { _rTargetTable :: TableName _rTargetTable = SourceTableName -> TableName forall source target. From source target => source -> target Witch.from SourceTableName _rTargetTable, _rRelationshipType :: RelationshipType _rRelationshipType = RelationshipType -> RelationshipType forall source target. From source target => source -> target Witch.from RelationshipType _rRelationshipType, _rColumnMapping :: HashMap SourceColumnName SourceColumnName _rColumnMapping = (SourceColumnName -> SourceColumnName) -> HashMap SourceColumnName SourceColumnName -> HashMap SourceColumnName SourceColumnName forall k2 k1 v. (Eq k2, Hashable k2) => (k1 -> k2) -> HashMap k1 v -> HashMap k2 v HashMap.mapKeys SourceColumnName -> SourceColumnName forall source target. From source target => source -> target Witch.from (HashMap SourceColumnName SourceColumnName -> HashMap SourceColumnName SourceColumnName) -> HashMap SourceColumnName SourceColumnName -> HashMap SourceColumnName SourceColumnName forall a b. (a -> b) -> a -> b $ SourceColumnName -> SourceColumnName forall source target. From source target => source -> target Witch.from (SourceColumnName -> SourceColumnName) -> HashMap SourceColumnName SourceColumnName -> HashMap SourceColumnName SourceColumnName forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> HashMap SourceColumnName SourceColumnName _rColumnMapping } instance Witch.From API.Relationship Relationship where from :: Relationship -> Relationship from API.Relationship {RelationshipType TableName HashMap SourceColumnName SourceColumnName _rColumnMapping :: HashMap SourceColumnName SourceColumnName _rRelationshipType :: RelationshipType _rTargetTable :: TableName _rColumnMapping :: Relationship -> HashMap SourceColumnName SourceColumnName _rRelationshipType :: Relationship -> RelationshipType _rTargetTable :: Relationship -> TableName ..} = Relationship :: SourceTableName -> RelationshipType -> HashMap SourceColumnName SourceColumnName -> Relationship Relationship { _rTargetTable :: SourceTableName _rTargetTable = TableName -> SourceTableName forall source target. From source target => source -> target Witch.from TableName _rTargetTable, _rRelationshipType :: RelationshipType _rRelationshipType = RelationshipType -> RelationshipType forall source target. From source target => source -> target Witch.from RelationshipType _rRelationshipType, _rColumnMapping :: HashMap SourceColumnName SourceColumnName _rColumnMapping = (SourceColumnName -> SourceColumnName) -> HashMap SourceColumnName SourceColumnName -> HashMap SourceColumnName SourceColumnName forall k2 k1 v. (Eq k2, Hashable k2) => (k1 -> k2) -> HashMap k1 v -> HashMap k2 v HashMap.mapKeys SourceColumnName -> SourceColumnName forall source target. From source target => source -> target Witch.from (HashMap SourceColumnName SourceColumnName -> HashMap SourceColumnName SourceColumnName) -> HashMap SourceColumnName SourceColumnName -> HashMap SourceColumnName SourceColumnName forall a b. (a -> b) -> a -> b $ SourceColumnName -> SourceColumnName forall source target. From source target => source -> target Witch.from (SourceColumnName -> SourceColumnName) -> HashMap SourceColumnName SourceColumnName -> HashMap SourceColumnName SourceColumnName forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> HashMap SourceColumnName SourceColumnName _rColumnMapping } data RelationshipType = ObjectRelationship | ArrayRelationship deriving stock (RelationshipType -> RelationshipType -> Bool (RelationshipType -> RelationshipType -> Bool) -> (RelationshipType -> RelationshipType -> Bool) -> Eq RelationshipType forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: RelationshipType -> RelationshipType -> Bool $c/= :: RelationshipType -> RelationshipType -> Bool == :: RelationshipType -> RelationshipType -> Bool $c== :: RelationshipType -> RelationshipType -> Bool Eq, Eq RelationshipType Eq RelationshipType -> (RelationshipType -> RelationshipType -> Ordering) -> (RelationshipType -> RelationshipType -> Bool) -> (RelationshipType -> RelationshipType -> Bool) -> (RelationshipType -> RelationshipType -> Bool) -> (RelationshipType -> RelationshipType -> Bool) -> (RelationshipType -> RelationshipType -> RelationshipType) -> (RelationshipType -> RelationshipType -> RelationshipType) -> Ord RelationshipType RelationshipType -> RelationshipType -> Bool RelationshipType -> RelationshipType -> Ordering RelationshipType -> RelationshipType -> RelationshipType 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 :: RelationshipType -> RelationshipType -> RelationshipType $cmin :: RelationshipType -> RelationshipType -> RelationshipType max :: RelationshipType -> RelationshipType -> RelationshipType $cmax :: RelationshipType -> RelationshipType -> RelationshipType >= :: RelationshipType -> RelationshipType -> Bool $c>= :: RelationshipType -> RelationshipType -> Bool > :: RelationshipType -> RelationshipType -> Bool $c> :: RelationshipType -> RelationshipType -> Bool <= :: RelationshipType -> RelationshipType -> Bool $c<= :: RelationshipType -> RelationshipType -> Bool < :: RelationshipType -> RelationshipType -> Bool $c< :: RelationshipType -> RelationshipType -> Bool compare :: RelationshipType -> RelationshipType -> Ordering $ccompare :: RelationshipType -> RelationshipType -> Ordering $cp1Ord :: Eq RelationshipType Ord, Int -> RelationshipType -> ShowS [RelationshipType] -> ShowS RelationshipType -> String (Int -> RelationshipType -> ShowS) -> (RelationshipType -> String) -> ([RelationshipType] -> ShowS) -> Show RelationshipType forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [RelationshipType] -> ShowS $cshowList :: [RelationshipType] -> ShowS show :: RelationshipType -> String $cshow :: RelationshipType -> String showsPrec :: Int -> RelationshipType -> ShowS $cshowsPrec :: Int -> RelationshipType -> ShowS Show, (forall x. RelationshipType -> Rep RelationshipType x) -> (forall x. Rep RelationshipType x -> RelationshipType) -> Generic RelationshipType forall x. Rep RelationshipType x -> RelationshipType forall x. RelationshipType -> Rep RelationshipType x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep RelationshipType x -> RelationshipType $cfrom :: forall x. RelationshipType -> Rep RelationshipType x Generic, Typeable RelationshipType DataType Constr Typeable RelationshipType -> (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RelationshipType -> c RelationshipType) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RelationshipType) -> (RelationshipType -> Constr) -> (RelationshipType -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RelationshipType)) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RelationshipType)) -> ((forall b. Data b => b -> b) -> RelationshipType -> RelationshipType) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RelationshipType -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RelationshipType -> r) -> (forall u. (forall d. Data d => d -> u) -> RelationshipType -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> RelationshipType -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> RelationshipType -> m RelationshipType) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> RelationshipType -> m RelationshipType) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> RelationshipType -> m RelationshipType) -> Data RelationshipType RelationshipType -> DataType RelationshipType -> Constr (forall b. Data b => b -> b) -> RelationshipType -> RelationshipType (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RelationshipType -> c RelationshipType (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RelationshipType forall a. Typeable a -> (forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> a -> c a) -> (forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a) -> (a -> Constr) -> (a -> DataType) -> (forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c a)) -> (forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a)) -> ((forall b. Data b => b -> b) -> a -> a) -> (forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r) -> (forall u. (forall d. Data d => d -> u) -> a -> [u]) -> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u) -> (forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> (forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> a -> m a) -> Data a forall u. Int -> (forall d. Data d => d -> u) -> RelationshipType -> u forall u. (forall d. Data d => d -> u) -> RelationshipType -> [u] forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RelationshipType -> r forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RelationshipType -> r forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> RelationshipType -> m RelationshipType forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> RelationshipType -> m RelationshipType forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RelationshipType forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RelationshipType -> c RelationshipType forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RelationshipType) forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RelationshipType) $cArrayRelationship :: Constr $cObjectRelationship :: Constr $tRelationshipType :: DataType gmapMo :: (forall d. Data d => d -> m d) -> RelationshipType -> m RelationshipType $cgmapMo :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> RelationshipType -> m RelationshipType gmapMp :: (forall d. Data d => d -> m d) -> RelationshipType -> m RelationshipType $cgmapMp :: forall (m :: * -> *). MonadPlus m => (forall d. Data d => d -> m d) -> RelationshipType -> m RelationshipType gmapM :: (forall d. Data d => d -> m d) -> RelationshipType -> m RelationshipType $cgmapM :: forall (m :: * -> *). Monad m => (forall d. Data d => d -> m d) -> RelationshipType -> m RelationshipType gmapQi :: Int -> (forall d. Data d => d -> u) -> RelationshipType -> u $cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RelationshipType -> u gmapQ :: (forall d. Data d => d -> u) -> RelationshipType -> [u] $cgmapQ :: forall u. (forall d. Data d => d -> u) -> RelationshipType -> [u] gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RelationshipType -> r $cgmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RelationshipType -> r gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RelationshipType -> r $cgmapQl :: forall r r'. (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RelationshipType -> r gmapT :: (forall b. Data b => b -> b) -> RelationshipType -> RelationshipType $cgmapT :: (forall b. Data b => b -> b) -> RelationshipType -> RelationshipType dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RelationshipType) $cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *). Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RelationshipType) dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c RelationshipType) $cdataCast1 :: forall (t :: * -> *) (c :: * -> *). Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RelationshipType) dataTypeOf :: RelationshipType -> DataType $cdataTypeOf :: RelationshipType -> DataType toConstr :: RelationshipType -> Constr $ctoConstr :: RelationshipType -> Constr gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RelationshipType $cgunfold :: forall (c :: * -> *). (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RelationshipType gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RelationshipType -> c RelationshipType $cgfoldl :: forall (c :: * -> *). (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RelationshipType -> c RelationshipType $cp1Data :: Typeable RelationshipType Data) instance ToJSON RelationshipType where toJSON :: RelationshipType -> Value toJSON = Options -> RelationshipType -> Value forall a. (Generic a, GToJSON' Value Zero (Rep a)) => Options -> a -> Value J.genericToJSON Options J.defaultOptions instance Witch.From RelationshipType API.RelationshipType where from :: RelationshipType -> RelationshipType from = \case RelationshipType ObjectRelationship -> RelationshipType API.ObjectRelationship RelationshipType ArrayRelationship -> RelationshipType API.ArrayRelationship instance Witch.From API.RelationshipType RelationshipType where from :: RelationshipType -> RelationshipType from = \case RelationshipType API.ObjectRelationship -> RelationshipType ObjectRelationship RelationshipType API.ArrayRelationship -> RelationshipType ArrayRelationship type SourceColumnName = IR.C.Name type TargetColumnName = IR.C.Name