{-# LANGUAGE ExistentialQuantification,DeriveGeneric,DeriveAnyClass,FlexibleInstances,OverloadedStrings, DeriveTraversable, DerivingVia, TemplateHaskell, TypeFamilies, BangPatterns #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module ProjectM36.Base where
import ProjectM36.DatabaseContextFunctionError
import ProjectM36.AtomFunctionError
import ProjectM36.MerkleHash
import Data.Functor.Foldable.TH
import qualified Data.Map as M
import qualified Data.HashSet as HS
import Data.Hashable (Hashable, hashWithSalt)
import qualified Data.Set as S
import Data.UUID (UUID)
import Control.DeepSeq (NFData, rnf)
import Control.DeepSeq.Generics (genericRnf)
import GHC.Generics (Generic)
import GHC.Stack
import qualified Data.Vector as V
import qualified Data.List as L
import Data.Text (Text)
import Data.Time.Clock
import Data.Time.Calendar (Day(..))
import Data.Typeable
import Data.ByteString (ByteString)
import qualified Data.List.NonEmpty as NE
import Data.Vector.Instances ()
import Data.Scientific
type StringType = Text
type DatabaseName = String
#if !(MIN_VERSION_hashable(1,3,4))
instance Hashable (M.Map TypeVarName AtomType) where
hashWithSalt salt tvmap = hashWithSalt salt (M.keys tvmap)
instance Hashable (M.Map AttributeName AtomExpr) where
hashWithSalt salt m = salt `hashWithSalt` M.toList m
instance Hashable (S.Set AttributeName) where
hashWithSalt salt s = salt `hashWithSalt` S.toList s
#endif
instance Hashable Day where
hashWithSalt :: Int -> Day -> Int
hashWithSalt Int
salt (ModifiedJulianDay Integer
d) = forall a. Hashable a => Int -> a -> Int
hashWithSalt Int
salt Integer
d
instance Hashable UTCTime where
hashWithSalt :: Int -> UTCTime -> Int
hashWithSalt Int
salt (UTCTime Day
d DiffTime
dt) =
Int
salt forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Day
d forall a. Hashable a => Int -> a -> Int
`hashWithSalt` DiffTime
dt
instance Hashable DiffTime where
hashWithSalt :: Int -> DiffTime -> Int
hashWithSalt Int
salt = forall a. Hashable a => Int -> a -> Int
hashWithSalt Int
salt forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Real a => a -> Rational
toRational
data Atom = IntegerAtom !Integer |
IntAtom !Int |
ScientificAtom !Scientific |
DoubleAtom !Double |
TextAtom !Text |
DayAtom !Day |
DateTimeAtom !UTCTime |
ByteStringAtom !ByteString |
BoolAtom !Bool |
UUIDAtom !UUID |
RelationAtom !Relation |
RelationalExprAtom !RelationalExpr |
SubrelationFoldAtom !Relation !AttributeName |
ConstructedAtom !DataConstructorName !AtomType [Atom]
deriving (Atom -> Atom -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Atom -> Atom -> Bool
$c/= :: Atom -> Atom -> Bool
== :: Atom -> Atom -> Bool
$c== :: Atom -> Atom -> Bool
Eq, Int -> Atom -> ShowS
[Atom] -> ShowS
Atom -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Atom] -> ShowS
$cshowList :: [Atom] -> ShowS
show :: Atom -> String
$cshow :: Atom -> String
showsPrec :: Int -> Atom -> ShowS
$cshowsPrec :: Int -> Atom -> ShowS
Show, Typeable, Atom -> ()
forall a. (a -> ()) -> NFData a
rnf :: Atom -> ()
$crnf :: Atom -> ()
NFData, forall x. Rep Atom x -> Atom
forall x. Atom -> Rep Atom x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Atom x -> Atom
$cfrom :: forall x. Atom -> Rep Atom x
Generic, ReadPrec [Atom]
ReadPrec Atom
Int -> ReadS Atom
ReadS [Atom]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Atom]
$creadListPrec :: ReadPrec [Atom]
readPrec :: ReadPrec Atom
$creadPrec :: ReadPrec Atom
readList :: ReadS [Atom]
$creadList :: ReadS [Atom]
readsPrec :: Int -> ReadS Atom
$creadsPrec :: Int -> ReadS Atom
Read)
instance Hashable Atom where
hashWithSalt :: Int -> Atom -> Int
hashWithSalt Int
salt (ConstructedAtom Text
dConsName AtomType
_ [Atom]
atoms) = Int
salt forall a. Hashable a => Int -> a -> Int
`hashWithSalt` [Atom]
atoms
forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Text
dConsName
hashWithSalt Int
salt (IntAtom Int
i) = Int
salt forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Int
i
hashWithSalt Int
salt (IntegerAtom Integer
i) = Int
salt forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Integer
i
hashWithSalt Int
salt (ScientificAtom Scientific
s) = Int
salt forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Scientific
s
hashWithSalt Int
salt (DoubleAtom Double
d) = Int
salt forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Double
d
hashWithSalt Int
salt (TextAtom Text
t) = Int
salt forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Text
t
hashWithSalt Int
salt (DayAtom Day
d) = Int
salt forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Day
d
hashWithSalt Int
salt (DateTimeAtom UTCTime
dt) = Int
salt forall a. Hashable a => Int -> a -> Int
`hashWithSalt` UTCTime
dt
hashWithSalt Int
salt (ByteStringAtom ByteString
bs) = Int
salt forall a. Hashable a => Int -> a -> Int
`hashWithSalt` ByteString
bs
hashWithSalt Int
salt (BoolAtom Bool
b) = Int
salt forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Bool
b
hashWithSalt Int
salt (UUIDAtom UUID
u) = Int
salt forall a. Hashable a => Int -> a -> Int
`hashWithSalt` UUID
u
hashWithSalt Int
salt (RelationAtom Relation
r) = Int
salt forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Relation
r
hashWithSalt Int
salt (RelationalExprAtom RelationalExpr
re) = Int
salt forall a. Hashable a => Int -> a -> Int
`hashWithSalt` RelationalExpr
re
hashWithSalt Int
salt (SubrelationFoldAtom Relation
rel Text
attrName) = Int
salt forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Relation
rel forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Text
attrName
data AtomType = IntAtomType |
IntegerAtomType |
ScientificAtomType |
DoubleAtomType |
TextAtomType |
DayAtomType |
DateTimeAtomType |
ByteStringAtomType |
BoolAtomType |
UUIDAtomType |
RelationAtomType Attributes |
SubrelationFoldAtomType AtomType |
ConstructedAtomType TypeConstructorName TypeVarMap |
RelationalExprAtomType |
TypeVariableType TypeVarName
deriving (AtomType -> AtomType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AtomType -> AtomType -> Bool
$c/= :: AtomType -> AtomType -> Bool
== :: AtomType -> AtomType -> Bool
$c== :: AtomType -> AtomType -> Bool
Eq, AtomType -> ()
forall a. (a -> ()) -> NFData a
rnf :: AtomType -> ()
$crnf :: AtomType -> ()
NFData, forall x. Rep AtomType x -> AtomType
forall x. AtomType -> Rep AtomType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AtomType x -> AtomType
$cfrom :: forall x. AtomType -> Rep AtomType x
Generic, Int -> AtomType -> ShowS
[AtomType] -> ShowS
AtomType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AtomType] -> ShowS
$cshowList :: [AtomType] -> ShowS
show :: AtomType -> String
$cshow :: AtomType -> String
showsPrec :: Int -> AtomType -> ShowS
$cshowsPrec :: Int -> AtomType -> ShowS
Show, ReadPrec [AtomType]
ReadPrec AtomType
Int -> ReadS AtomType
ReadS [AtomType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AtomType]
$creadListPrec :: ReadPrec [AtomType]
readPrec :: ReadPrec AtomType
$creadPrec :: ReadPrec AtomType
readList :: ReadS [AtomType]
$creadList :: ReadS [AtomType]
readsPrec :: Int -> ReadS AtomType
$creadsPrec :: Int -> ReadS AtomType
Read, Eq AtomType
Int -> AtomType -> Int
AtomType -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: AtomType -> Int
$chash :: AtomType -> Int
hashWithSalt :: Int -> AtomType -> Int
$chashWithSalt :: Int -> AtomType -> Int
Hashable)
type TypeVarMap = M.Map TypeVarName AtomType
isRelationAtomType :: AtomType -> Bool
isRelationAtomType :: AtomType -> Bool
isRelationAtomType (RelationAtomType Attributes
_) = Bool
True
isRelationAtomType AtomType
_ = Bool
False
attributesContainRelationAtomType :: Attributes -> Bool
attributesContainRelationAtomType :: Attributes -> Bool
attributesContainRelationAtomType Attributes
attrs = forall a. Vector a -> Bool
V.null (forall a. (a -> Bool) -> Vector a -> Vector a
V.filter (\(Attribute Text
_ AtomType
t) -> AtomType -> Bool
isRelationAtomType AtomType
t) (Attributes -> Vector Attribute
attributesVec Attributes
attrs))
type AttributeName = StringType
data Attribute = Attribute AttributeName AtomType deriving (Attribute -> Attribute -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Attribute -> Attribute -> Bool
$c/= :: Attribute -> Attribute -> Bool
== :: Attribute -> Attribute -> Bool
$c== :: Attribute -> Attribute -> Bool
Eq, Int -> Attribute -> ShowS
[Attribute] -> ShowS
Attribute -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Attribute] -> ShowS
$cshowList :: [Attribute] -> ShowS
show :: Attribute -> String
$cshow :: Attribute -> String
showsPrec :: Int -> Attribute -> ShowS
$cshowsPrec :: Int -> Attribute -> ShowS
Show, ReadPrec [Attribute]
ReadPrec Attribute
Int -> ReadS Attribute
ReadS [Attribute]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Attribute]
$creadListPrec :: ReadPrec [Attribute]
readPrec :: ReadPrec Attribute
$creadPrec :: ReadPrec Attribute
readList :: ReadS [Attribute]
$creadList :: ReadS [Attribute]
readsPrec :: Int -> ReadS Attribute
$creadsPrec :: Int -> ReadS Attribute
Read, forall x. Rep Attribute x -> Attribute
forall x. Attribute -> Rep Attribute x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Attribute x -> Attribute
$cfrom :: forall x. Attribute -> Rep Attribute x
Generic, Attribute -> ()
forall a. (a -> ()) -> NFData a
rnf :: Attribute -> ()
$crnf :: Attribute -> ()
NFData)
instance Hashable Attribute where
hashWithSalt :: Int -> Attribute -> Int
hashWithSalt Int
salt (Attribute Text
attrName AtomType
_) = forall a. Hashable a => Int -> a -> Int
hashWithSalt Int
salt Text
attrName
type AttributesHash = Int
newtype Attributes = Attributes {
Attributes -> Vector Attribute
attributesVec :: V.Vector Attribute
}
deriving (Attributes -> ()
forall a. (a -> ()) -> NFData a
rnf :: Attributes -> ()
$crnf :: Attributes -> ()
NFData, ReadPrec [Attributes]
ReadPrec Attributes
Int -> ReadS Attributes
ReadS [Attributes]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Attributes]
$creadListPrec :: ReadPrec [Attributes]
readPrec :: ReadPrec Attributes
$creadPrec :: ReadPrec Attributes
readList :: ReadS [Attributes]
$creadList :: ReadS [Attributes]
readsPrec :: Int -> ReadS Attributes
$creadsPrec :: Int -> ReadS Attributes
Read, Eq Attributes
Int -> Attributes -> Int
Attributes -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: Attributes -> Int
$chash :: Attributes -> Int
hashWithSalt :: Int -> Attributes -> Int
$chashWithSalt :: Int -> Attributes -> Int
Hashable, forall x. Rep Attributes x -> Attributes
forall x. Attributes -> Rep Attributes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Attributes x -> Attributes
$cfrom :: forall x. Attributes -> Rep Attributes x
Generic)
attributesSet :: Attributes -> HS.HashSet Attribute
attributesSet :: Attributes -> HashSet Attribute
attributesSet = forall a. (Eq a, Hashable a) => [a] -> HashSet a
HS.fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Vector a -> [a]
V.toList forall b c a. (b -> c) -> (a -> b) -> a -> c
. Attributes -> Vector Attribute
attributesVec
instance Show Attributes where
showsPrec :: Int -> Attributes -> ShowS
showsPrec Int
d Attributes
attrs = String -> ShowS
showString forall a b. (a -> b) -> a -> b
$ ShowS
parens forall a b. (a -> b) -> a -> b
$ String
"attributesFromList [" forall a. Semigroup a => a -> a -> a
<> forall a. [a] -> [[a]] -> [a]
L.intercalate String
", " (forall a b. (a -> b) -> [a] -> [b]
map (\Attribute
attr -> String
"(" forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show Attribute
attr forall a. Semigroup a => a -> a -> a
<> String
")") (forall a. Vector a -> [a]
V.toList (Attributes -> Vector Attribute
attributesVec Attributes
attrs))) forall a. Semigroup a => a -> a -> a
<> String
"]"
where parens :: ShowS
parens String
x | Int
d forall a. Ord a => a -> a -> Bool
> Int
0 = String
"(" forall a. Semigroup a => a -> a -> a
<> String
x forall a. Semigroup a => a -> a -> a
<> String
")"
parens String
x = String
x
instance Eq Attributes where
Attributes
attrsA == :: Attributes -> Attributes -> Bool
== Attributes
attrsB =
Attributes -> Vector Attribute
attributesVec Attributes
attrsA forall a. Eq a => a -> a -> Bool
== Attributes -> Vector Attribute
attributesVec Attributes
attrsB Bool -> Bool -> Bool
||
Attributes -> HashSet Attribute
attributesSet Attributes
attrsA forall a. Eq a => a -> a -> Bool
== Attributes -> HashSet Attribute
attributesSet Attributes
attrsB
sortedAttributesIndices :: Attributes -> [(Int, Attribute)]
sortedAttributesIndices :: Attributes -> [(Int, Attribute)]
sortedAttributesIndices Attributes
attrs = forall a. (a -> a -> Ordering) -> [a] -> [a]
L.sortBy (\(Int
_, Attribute Text
name1 AtomType
_) (Int
_,Attribute Text
name2 AtomType
_) -> forall a. Ord a => a -> a -> Ordering
compare Text
name1 Text
name2) forall a b. (a -> b) -> a -> b
$ forall a. Vector a -> [a]
V.toList (forall a. Vector a -> Vector (Int, a)
V.indexed (Attributes -> Vector Attribute
attributesVec Attributes
attrs))
newtype RelationTupleSet = RelationTupleSet { RelationTupleSet -> [RelationTuple]
asList :: [RelationTuple] } deriving (Int -> RelationTupleSet -> ShowS
[RelationTupleSet] -> ShowS
RelationTupleSet -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RelationTupleSet] -> ShowS
$cshowList :: [RelationTupleSet] -> ShowS
show :: RelationTupleSet -> String
$cshow :: RelationTupleSet -> String
showsPrec :: Int -> RelationTupleSet -> ShowS
$cshowsPrec :: Int -> RelationTupleSet -> ShowS
Show, forall x. Rep RelationTupleSet x -> RelationTupleSet
forall x. RelationTupleSet -> Rep RelationTupleSet x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RelationTupleSet x -> RelationTupleSet
$cfrom :: forall x. RelationTupleSet -> Rep RelationTupleSet x
Generic, ReadPrec [RelationTupleSet]
ReadPrec RelationTupleSet
Int -> ReadS RelationTupleSet
ReadS [RelationTupleSet]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RelationTupleSet]
$creadListPrec :: ReadPrec [RelationTupleSet]
readPrec :: ReadPrec RelationTupleSet
$creadPrec :: ReadPrec RelationTupleSet
readList :: ReadS [RelationTupleSet]
$creadList :: ReadS [RelationTupleSet]
readsPrec :: Int -> ReadS RelationTupleSet
$creadsPrec :: Int -> ReadS RelationTupleSet
Read)
instance Hashable RelationTupleSet where
hashWithSalt :: Int -> RelationTupleSet -> Int
hashWithSalt Int
s RelationTupleSet
tupSet = forall a. Hashable a => Int -> a -> Int
hashWithSalt Int
s (forall a. (Eq a, Hashable a) => [a] -> HashSet a
HS.fromList (RelationTupleSet -> [RelationTuple]
asList RelationTupleSet
tupSet))
instance Read Relation where
readsPrec :: Int -> ReadS Relation
readsPrec = forall a. HasCallStack => String -> a
error String
"relation read not supported"
instance Eq RelationTupleSet where
RelationTupleSet
set1 == :: RelationTupleSet -> RelationTupleSet -> Bool
== RelationTupleSet
set2 = RelationTupleSet -> HashSet RelationTuple
hset RelationTupleSet
set1 forall a. Eq a => a -> a -> Bool
== RelationTupleSet -> HashSet RelationTuple
hset RelationTupleSet
set2
where
hset :: RelationTupleSet -> HashSet RelationTuple
hset = forall a. (Eq a, Hashable a) => [a] -> HashSet a
HS.fromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. RelationTupleSet -> [RelationTuple]
asList
instance NFData RelationTupleSet where rnf :: RelationTupleSet -> ()
rnf = forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Hashable RelationTuple where
hashWithSalt :: Int -> RelationTuple -> Int
hashWithSalt Int
salt (RelationTuple Attributes
attrs Vector Atom
tupVec) = if forall a. Vector a -> Int
V.length (Attributes -> Vector Attribute
attributesVec Attributes
attrs) forall a. Eq a => a -> a -> Bool
/= forall a. Vector a -> Int
V.length Vector Atom
tupVec then
forall a. HasCallStack => String -> a
error (String
"invalid tuple: attributes and tuple count mismatch " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show (Attributes -> Vector Attribute
attributesVec Attributes
attrs, Vector Atom
tupVec))
else
Int
salt forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
[Attribute]
sortedAttrs forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
forall a. Vector a -> [a]
V.toList Vector Atom
sortedTupVec
where
sortedAttrsIndices :: [(Int, Attribute)]
sortedAttrsIndices = Attributes -> [(Int, Attribute)]
sortedAttributesIndices Attributes
attrs
sortedAttrs :: [Attribute]
sortedAttrs = forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> b
snd [(Int, Attribute)]
sortedAttrsIndices
sortedTupVec :: Vector Atom
sortedTupVec = forall a b. (a -> b) -> Vector a -> Vector b
V.map (\(Int
index, Attribute
_) -> Vector Atom
tupVec forall a. Vector a -> Int -> a
V.! Int
index) forall a b. (a -> b) -> a -> b
$ forall a. [a] -> Vector a
V.fromList [(Int, Attribute)]
sortedAttrsIndices
data RelationTuple = RelationTuple Attributes (V.Vector Atom) deriving (Int -> RelationTuple -> ShowS
[RelationTuple] -> ShowS
RelationTuple -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RelationTuple] -> ShowS
$cshowList :: [RelationTuple] -> ShowS
show :: RelationTuple -> String
$cshow :: RelationTuple -> String
showsPrec :: Int -> RelationTuple -> ShowS
$cshowsPrec :: Int -> RelationTuple -> ShowS
Show, ReadPrec [RelationTuple]
ReadPrec RelationTuple
Int -> ReadS RelationTuple
ReadS [RelationTuple]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RelationTuple]
$creadListPrec :: ReadPrec [RelationTuple]
readPrec :: ReadPrec RelationTuple
$creadPrec :: ReadPrec RelationTuple
readList :: ReadS [RelationTuple]
$creadList :: ReadS [RelationTuple]
readsPrec :: Int -> ReadS RelationTuple
$creadsPrec :: Int -> ReadS RelationTuple
Read, forall x. Rep RelationTuple x -> RelationTuple
forall x. RelationTuple -> Rep RelationTuple x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RelationTuple x -> RelationTuple
$cfrom :: forall x. RelationTuple -> Rep RelationTuple x
Generic)
instance Eq RelationTuple where
tuple1 :: RelationTuple
tuple1@(RelationTuple Attributes
attrs1 Vector Atom
_) == :: RelationTuple -> RelationTuple -> Bool
== tuple2 :: RelationTuple
tuple2@(RelationTuple Attributes
attrs2 Vector Atom
_) =
Attributes
attrs1 forall a. Eq a => a -> a -> Bool
== Attributes
attrs2 Bool -> Bool -> Bool
&& Bool
atomsEqual
where
atomForAttribute :: Attribute -> RelationTuple -> Maybe Atom
atomForAttribute Attribute
attr (RelationTuple Attributes
attrs Vector Atom
tupVec) = case forall a. (a -> Bool) -> Vector a -> Maybe Int
V.findIndex (forall a. Eq a => a -> a -> Bool
== Attribute
attr) (Attributes -> Vector Attribute
attributesVec Attributes
attrs) of
Maybe Int
Nothing -> forall a. Maybe a
Nothing
Just Int
index -> Vector Atom
tupVec forall a. Vector a -> Int -> Maybe a
V.!? Int
index
atomsEqual :: Bool
atomsEqual = forall a. (a -> Bool) -> Vector a -> Bool
V.all forall a. a -> a
id forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> Vector a -> Vector b
V.map (\Attribute
attr -> Attribute -> RelationTuple -> Maybe Atom
atomForAttribute Attribute
attr RelationTuple
tuple1 forall a. Eq a => a -> a -> Bool
== Attribute -> RelationTuple -> Maybe Atom
atomForAttribute Attribute
attr RelationTuple
tuple2) (Attributes -> Vector Attribute
attributesVec Attributes
attrs1)
instance NFData RelationTuple where rnf :: RelationTuple -> ()
rnf = forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
data Relation = Relation Attributes RelationTupleSet deriving (Int -> Relation -> ShowS
[Relation] -> ShowS
Relation -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Relation] -> ShowS
$cshowList :: [Relation] -> ShowS
show :: Relation -> String
$cshow :: Relation -> String
showsPrec :: Int -> Relation -> ShowS
$cshowsPrec :: Int -> Relation -> ShowS
Show, forall x. Rep Relation x -> Relation
forall x. Relation -> Rep Relation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Relation x -> Relation
$cfrom :: forall x. Relation -> Rep Relation x
Generic,Typeable)
instance Eq Relation where
Relation Attributes
attrs1 RelationTupleSet
tupSet1 == :: Relation -> Relation -> Bool
== Relation Attributes
attrs2 RelationTupleSet
tupSet2 = Attributes
attrs1 forall a. Eq a => a -> a -> Bool
== Attributes
attrs2 Bool -> Bool -> Bool
&& RelationTupleSet
tupSet1 forall a. Eq a => a -> a -> Bool
== RelationTupleSet
tupSet2
instance NFData Relation where rnf :: Relation -> ()
rnf = forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf
instance Hashable Relation where
hashWithSalt :: Int -> Relation -> Int
hashWithSalt Int
salt (Relation Attributes
attrs RelationTupleSet
tupSet) = Int
salt forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
[Attribute]
sortedAttrs forall a. Hashable a => Int -> a -> Int
`hashWithSalt`
forall a. (Eq a, Hashable a) => [a] -> HashSet a
HS.fromList (RelationTupleSet -> [RelationTuple]
asList RelationTupleSet
tupSet)
where
sortedAttrs :: [Attribute]
sortedAttrs = forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> b
snd (Attributes -> [(Int, Attribute)]
sortedAttributesIndices Attributes
attrs)
data RelationCardinality = Countable | Finite Int deriving (RelationCardinality -> RelationCardinality -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RelationCardinality -> RelationCardinality -> Bool
$c/= :: RelationCardinality -> RelationCardinality -> Bool
== :: RelationCardinality -> RelationCardinality -> Bool
$c== :: RelationCardinality -> RelationCardinality -> Bool
Eq, Int -> RelationCardinality -> ShowS
[RelationCardinality] -> ShowS
RelationCardinality -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RelationCardinality] -> ShowS
$cshowList :: [RelationCardinality] -> ShowS
show :: RelationCardinality -> String
$cshow :: RelationCardinality -> String
showsPrec :: Int -> RelationCardinality -> ShowS
$cshowsPrec :: Int -> RelationCardinality -> ShowS
Show, forall x. Rep RelationCardinality x -> RelationCardinality
forall x. RelationCardinality -> Rep RelationCardinality x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RelationCardinality x -> RelationCardinality
$cfrom :: forall x. RelationCardinality -> Rep RelationCardinality x
Generic, Eq RelationCardinality
RelationCardinality -> RelationCardinality -> Bool
RelationCardinality -> RelationCardinality -> Ordering
RelationCardinality -> RelationCardinality -> RelationCardinality
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 :: RelationCardinality -> RelationCardinality -> RelationCardinality
$cmin :: RelationCardinality -> RelationCardinality -> RelationCardinality
max :: RelationCardinality -> RelationCardinality -> RelationCardinality
$cmax :: RelationCardinality -> RelationCardinality -> RelationCardinality
>= :: RelationCardinality -> RelationCardinality -> Bool
$c>= :: RelationCardinality -> RelationCardinality -> Bool
> :: RelationCardinality -> RelationCardinality -> Bool
$c> :: RelationCardinality -> RelationCardinality -> Bool
<= :: RelationCardinality -> RelationCardinality -> Bool
$c<= :: RelationCardinality -> RelationCardinality -> Bool
< :: RelationCardinality -> RelationCardinality -> Bool
$c< :: RelationCardinality -> RelationCardinality -> Bool
compare :: RelationCardinality -> RelationCardinality -> Ordering
$ccompare :: RelationCardinality -> RelationCardinality -> Ordering
Ord)
type RelVarName = StringType
type RelationalExpr = RelationalExprBase ()
data RelationalExprBase a =
MakeRelationFromExprs (Maybe [AttributeExprBase a]) (TupleExprsBase a) |
MakeStaticRelation Attributes RelationTupleSet |
ExistingRelation Relation |
RelationVariable RelVarName a |
RelationValuedAttribute AttributeName |
Project (AttributeNamesBase a) (RelationalExprBase a) |
Union (RelationalExprBase a) (RelationalExprBase a) |
Join (RelationalExprBase a) (RelationalExprBase a) |
Rename (S.Set (AttributeName, AttributeName)) (RelationalExprBase a) |
Difference (RelationalExprBase a) (RelationalExprBase a) |
Group (AttributeNamesBase a) AttributeName (RelationalExprBase a) |
Ungroup AttributeName (RelationalExprBase a) |
Restrict (RestrictionPredicateExprBase a) (RelationalExprBase a) |
Equals (RelationalExprBase a) (RelationalExprBase a) |
NotEquals (RelationalExprBase a) (RelationalExprBase a) |
Extend (ExtendTupleExprBase a) (RelationalExprBase a) |
With (WithNamesAssocsBase a) (RelationalExprBase a)
deriving (Int -> RelationalExprBase a -> ShowS
forall a. Show a => Int -> RelationalExprBase a -> ShowS
forall a. Show a => [RelationalExprBase a] -> ShowS
forall a. Show a => RelationalExprBase a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RelationalExprBase a] -> ShowS
$cshowList :: forall a. Show a => [RelationalExprBase a] -> ShowS
show :: RelationalExprBase a -> String
$cshow :: forall a. Show a => RelationalExprBase a -> String
showsPrec :: Int -> RelationalExprBase a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> RelationalExprBase a -> ShowS
Show, ReadPrec [RelationalExprBase a]
ReadPrec (RelationalExprBase a)
ReadS [RelationalExprBase a]
forall a. Read a => ReadPrec [RelationalExprBase a]
forall a. Read a => ReadPrec (RelationalExprBase a)
forall a. Read a => Int -> ReadS (RelationalExprBase a)
forall a. Read a => ReadS [RelationalExprBase a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RelationalExprBase a]
$creadListPrec :: forall a. Read a => ReadPrec [RelationalExprBase a]
readPrec :: ReadPrec (RelationalExprBase a)
$creadPrec :: forall a. Read a => ReadPrec (RelationalExprBase a)
readList :: ReadS [RelationalExprBase a]
$creadList :: forall a. Read a => ReadS [RelationalExprBase a]
readsPrec :: Int -> ReadS (RelationalExprBase a)
$creadsPrec :: forall a. Read a => Int -> ReadS (RelationalExprBase a)
Read, RelationalExprBase a -> RelationalExprBase a -> Bool
forall a.
Eq a =>
RelationalExprBase a -> RelationalExprBase a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RelationalExprBase a -> RelationalExprBase a -> Bool
$c/= :: forall a.
Eq a =>
RelationalExprBase a -> RelationalExprBase a -> Bool
== :: RelationalExprBase a -> RelationalExprBase a -> Bool
$c== :: forall a.
Eq a =>
RelationalExprBase a -> RelationalExprBase a -> Bool
Eq, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (RelationalExprBase a) x -> RelationalExprBase a
forall a x. RelationalExprBase a -> Rep (RelationalExprBase a) x
$cto :: forall a x. Rep (RelationalExprBase a) x -> RelationalExprBase a
$cfrom :: forall a x. RelationalExprBase a -> Rep (RelationalExprBase a) x
Generic, forall a. NFData a => RelationalExprBase a -> ()
forall a. (a -> ()) -> NFData a
rnf :: RelationalExprBase a -> ()
$crnf :: forall a. NFData a => RelationalExprBase a -> ()
NFData, forall a. Eq a => a -> RelationalExprBase a -> Bool
forall a. Num a => RelationalExprBase a -> a
forall a. Ord a => RelationalExprBase a -> a
forall m. Monoid m => RelationalExprBase m -> m
forall a. RelationalExprBase a -> Bool
forall a. RelationalExprBase a -> Int
forall a. RelationalExprBase a -> [a]
forall a. (a -> a -> a) -> RelationalExprBase a -> a
forall m a. Monoid m => (a -> m) -> RelationalExprBase a -> m
forall b a. (b -> a -> b) -> b -> RelationalExprBase a -> b
forall a b. (a -> b -> b) -> b -> RelationalExprBase a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: forall a. Num a => RelationalExprBase a -> a
$cproduct :: forall a. Num a => RelationalExprBase a -> a
sum :: forall a. Num a => RelationalExprBase a -> a
$csum :: forall a. Num a => RelationalExprBase a -> a
minimum :: forall a. Ord a => RelationalExprBase a -> a
$cminimum :: forall a. Ord a => RelationalExprBase a -> a
maximum :: forall a. Ord a => RelationalExprBase a -> a
$cmaximum :: forall a. Ord a => RelationalExprBase a -> a
elem :: forall a. Eq a => a -> RelationalExprBase a -> Bool
$celem :: forall a. Eq a => a -> RelationalExprBase a -> Bool
length :: forall a. RelationalExprBase a -> Int
$clength :: forall a. RelationalExprBase a -> Int
null :: forall a. RelationalExprBase a -> Bool
$cnull :: forall a. RelationalExprBase a -> Bool
toList :: forall a. RelationalExprBase a -> [a]
$ctoList :: forall a. RelationalExprBase a -> [a]
foldl1 :: forall a. (a -> a -> a) -> RelationalExprBase a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> RelationalExprBase a -> a
foldr1 :: forall a. (a -> a -> a) -> RelationalExprBase a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> RelationalExprBase a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> RelationalExprBase a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> RelationalExprBase a -> b
foldl :: forall b a. (b -> a -> b) -> b -> RelationalExprBase a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> RelationalExprBase a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> RelationalExprBase a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> RelationalExprBase a -> b
foldr :: forall a b. (a -> b -> b) -> b -> RelationalExprBase a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> RelationalExprBase a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> RelationalExprBase a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> RelationalExprBase a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> RelationalExprBase a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> RelationalExprBase a -> m
fold :: forall m. Monoid m => RelationalExprBase m -> m
$cfold :: forall m. Monoid m => RelationalExprBase m -> m
Foldable, forall a b. a -> RelationalExprBase b -> RelationalExprBase a
forall a b.
(a -> b) -> RelationalExprBase a -> RelationalExprBase b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> RelationalExprBase b -> RelationalExprBase a
$c<$ :: forall a b. a -> RelationalExprBase b -> RelationalExprBase a
fmap :: forall a b.
(a -> b) -> RelationalExprBase a -> RelationalExprBase b
$cfmap :: forall a b.
(a -> b) -> RelationalExprBase a -> RelationalExprBase b
Functor, Functor RelationalExprBase
Foldable RelationalExprBase
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
RelationalExprBase (m a) -> m (RelationalExprBase a)
forall (f :: * -> *) a.
Applicative f =>
RelationalExprBase (f a) -> f (RelationalExprBase a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> RelationalExprBase a -> m (RelationalExprBase b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> RelationalExprBase a -> f (RelationalExprBase b)
sequence :: forall (m :: * -> *) a.
Monad m =>
RelationalExprBase (m a) -> m (RelationalExprBase a)
$csequence :: forall (m :: * -> *) a.
Monad m =>
RelationalExprBase (m a) -> m (RelationalExprBase a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> RelationalExprBase a -> m (RelationalExprBase b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> RelationalExprBase a -> m (RelationalExprBase b)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
RelationalExprBase (f a) -> f (RelationalExprBase a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
RelationalExprBase (f a) -> f (RelationalExprBase a)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> RelationalExprBase a -> f (RelationalExprBase b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> RelationalExprBase a -> f (RelationalExprBase b)
Traversable)
instance Hashable RelationalExpr
type WithNamesAssocs = WithNamesAssocsBase ()
type WithNamesAssocsBase a = [(WithNameExprBase a, RelationalExprBase a)]
type GraphRefWithNameAssocs = [(GraphRefWithNameExpr, GraphRefRelationalExpr)]
data WithNameExprBase a = WithNameExpr RelVarName a
deriving (Int -> WithNameExprBase a -> ShowS
forall a. Show a => Int -> WithNameExprBase a -> ShowS
forall a. Show a => [WithNameExprBase a] -> ShowS
forall a. Show a => WithNameExprBase a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WithNameExprBase a] -> ShowS
$cshowList :: forall a. Show a => [WithNameExprBase a] -> ShowS
show :: WithNameExprBase a -> String
$cshow :: forall a. Show a => WithNameExprBase a -> String
showsPrec :: Int -> WithNameExprBase a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> WithNameExprBase a -> ShowS
Show, ReadPrec [WithNameExprBase a]
ReadPrec (WithNameExprBase a)
ReadS [WithNameExprBase a]
forall a. Read a => ReadPrec [WithNameExprBase a]
forall a. Read a => ReadPrec (WithNameExprBase a)
forall a. Read a => Int -> ReadS (WithNameExprBase a)
forall a. Read a => ReadS [WithNameExprBase a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WithNameExprBase a]
$creadListPrec :: forall a. Read a => ReadPrec [WithNameExprBase a]
readPrec :: ReadPrec (WithNameExprBase a)
$creadPrec :: forall a. Read a => ReadPrec (WithNameExprBase a)
readList :: ReadS [WithNameExprBase a]
$creadList :: forall a. Read a => ReadS [WithNameExprBase a]
readsPrec :: Int -> ReadS (WithNameExprBase a)
$creadsPrec :: forall a. Read a => Int -> ReadS (WithNameExprBase a)
Read, WithNameExprBase a -> WithNameExprBase a -> Bool
forall a. Eq a => WithNameExprBase a -> WithNameExprBase a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WithNameExprBase a -> WithNameExprBase a -> Bool
$c/= :: forall a. Eq a => WithNameExprBase a -> WithNameExprBase a -> Bool
== :: WithNameExprBase a -> WithNameExprBase a -> Bool
$c== :: forall a. Eq a => WithNameExprBase a -> WithNameExprBase a -> Bool
Eq, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (WithNameExprBase a) x -> WithNameExprBase a
forall a x. WithNameExprBase a -> Rep (WithNameExprBase a) x
$cto :: forall a x. Rep (WithNameExprBase a) x -> WithNameExprBase a
$cfrom :: forall a x. WithNameExprBase a -> Rep (WithNameExprBase a) x
Generic, forall a. NFData a => WithNameExprBase a -> ()
forall a. (a -> ()) -> NFData a
rnf :: WithNameExprBase a -> ()
$crnf :: forall a. NFData a => WithNameExprBase a -> ()
NFData, forall a. Eq a => a -> WithNameExprBase a -> Bool
forall a. Num a => WithNameExprBase a -> a
forall a. Ord a => WithNameExprBase a -> a
forall m. Monoid m => WithNameExprBase m -> m
forall a. WithNameExprBase a -> Bool
forall a. WithNameExprBase a -> Int
forall a. WithNameExprBase a -> [a]
forall a. (a -> a -> a) -> WithNameExprBase a -> a
forall m a. Monoid m => (a -> m) -> WithNameExprBase a -> m
forall b a. (b -> a -> b) -> b -> WithNameExprBase a -> b
forall a b. (a -> b -> b) -> b -> WithNameExprBase a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: forall a. Num a => WithNameExprBase a -> a
$cproduct :: forall a. Num a => WithNameExprBase a -> a
sum :: forall a. Num a => WithNameExprBase a -> a
$csum :: forall a. Num a => WithNameExprBase a -> a
minimum :: forall a. Ord a => WithNameExprBase a -> a
$cminimum :: forall a. Ord a => WithNameExprBase a -> a
maximum :: forall a. Ord a => WithNameExprBase a -> a
$cmaximum :: forall a. Ord a => WithNameExprBase a -> a
elem :: forall a. Eq a => a -> WithNameExprBase a -> Bool
$celem :: forall a. Eq a => a -> WithNameExprBase a -> Bool
length :: forall a. WithNameExprBase a -> Int
$clength :: forall a. WithNameExprBase a -> Int
null :: forall a. WithNameExprBase a -> Bool
$cnull :: forall a. WithNameExprBase a -> Bool
toList :: forall a. WithNameExprBase a -> [a]
$ctoList :: forall a. WithNameExprBase a -> [a]
foldl1 :: forall a. (a -> a -> a) -> WithNameExprBase a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> WithNameExprBase a -> a
foldr1 :: forall a. (a -> a -> a) -> WithNameExprBase a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> WithNameExprBase a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> WithNameExprBase a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> WithNameExprBase a -> b
foldl :: forall b a. (b -> a -> b) -> b -> WithNameExprBase a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> WithNameExprBase a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> WithNameExprBase a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> WithNameExprBase a -> b
foldr :: forall a b. (a -> b -> b) -> b -> WithNameExprBase a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> WithNameExprBase a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> WithNameExprBase a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> WithNameExprBase a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> WithNameExprBase a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> WithNameExprBase a -> m
fold :: forall m. Monoid m => WithNameExprBase m -> m
$cfold :: forall m. Monoid m => WithNameExprBase m -> m
Foldable, forall a b. a -> WithNameExprBase b -> WithNameExprBase a
forall a b. (a -> b) -> WithNameExprBase a -> WithNameExprBase b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> WithNameExprBase b -> WithNameExprBase a
$c<$ :: forall a b. a -> WithNameExprBase b -> WithNameExprBase a
fmap :: forall a b. (a -> b) -> WithNameExprBase a -> WithNameExprBase b
$cfmap :: forall a b. (a -> b) -> WithNameExprBase a -> WithNameExprBase b
Functor, Functor WithNameExprBase
Foldable WithNameExprBase
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
WithNameExprBase (m a) -> m (WithNameExprBase a)
forall (f :: * -> *) a.
Applicative f =>
WithNameExprBase (f a) -> f (WithNameExprBase a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> WithNameExprBase a -> m (WithNameExprBase b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> WithNameExprBase a -> f (WithNameExprBase b)
sequence :: forall (m :: * -> *) a.
Monad m =>
WithNameExprBase (m a) -> m (WithNameExprBase a)
$csequence :: forall (m :: * -> *) a.
Monad m =>
WithNameExprBase (m a) -> m (WithNameExprBase a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> WithNameExprBase a -> m (WithNameExprBase b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> WithNameExprBase a -> m (WithNameExprBase b)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
WithNameExprBase (f a) -> f (WithNameExprBase a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
WithNameExprBase (f a) -> f (WithNameExprBase a)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> WithNameExprBase a -> f (WithNameExprBase b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> WithNameExprBase a -> f (WithNameExprBase b)
Traversable, forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
forall {a}. Hashable a => Eq (WithNameExprBase a)
forall a. Hashable a => Int -> WithNameExprBase a -> Int
forall a. Hashable a => WithNameExprBase a -> Int
hash :: WithNameExprBase a -> Int
$chash :: forall a. Hashable a => WithNameExprBase a -> Int
hashWithSalt :: Int -> WithNameExprBase a -> Int
$chashWithSalt :: forall a. Hashable a => Int -> WithNameExprBase a -> Int
Hashable)
type WithNameExpr = WithNameExprBase ()
type GraphRefWithNameExpr = WithNameExprBase GraphRefTransactionMarker
type NotificationName = StringType
type Notifications = M.Map NotificationName Notification
data Notification = Notification {
Notification -> RelationalExpr
changeExpr :: RelationalExpr,
Notification -> RelationalExpr
reportOldExpr :: RelationalExpr,
Notification -> RelationalExpr
reportNewExpr :: RelationalExpr
}
deriving (Int -> Notification -> ShowS
[Notification] -> ShowS
Notification -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Notification] -> ShowS
$cshowList :: [Notification] -> ShowS
show :: Notification -> String
$cshow :: Notification -> String
showsPrec :: Int -> Notification -> ShowS
$cshowsPrec :: Int -> Notification -> ShowS
Show, Notification -> Notification -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Notification -> Notification -> Bool
$c/= :: Notification -> Notification -> Bool
== :: Notification -> Notification -> Bool
$c== :: Notification -> Notification -> Bool
Eq, forall x. Rep Notification x -> Notification
forall x. Notification -> Rep Notification x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Notification x -> Notification
$cfrom :: forall x. Notification -> Rep Notification x
Generic, Notification -> ()
forall a. (a -> ()) -> NFData a
rnf :: Notification -> ()
$crnf :: Notification -> ()
NFData)
data NotificationExpression = NotificationChangeExpression |
NotificationReportOldExpression |
NotificationReportNewExpression
deriving (Int -> NotificationExpression -> ShowS
[NotificationExpression] -> ShowS
NotificationExpression -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NotificationExpression] -> ShowS
$cshowList :: [NotificationExpression] -> ShowS
show :: NotificationExpression -> String
$cshow :: NotificationExpression -> String
showsPrec :: Int -> NotificationExpression -> ShowS
$cshowsPrec :: Int -> NotificationExpression -> ShowS
Show, NotificationExpression -> NotificationExpression -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NotificationExpression -> NotificationExpression -> Bool
$c/= :: NotificationExpression -> NotificationExpression -> Bool
== :: NotificationExpression -> NotificationExpression -> Bool
$c== :: NotificationExpression -> NotificationExpression -> Bool
Eq, forall x. Rep NotificationExpression x -> NotificationExpression
forall x. NotificationExpression -> Rep NotificationExpression x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NotificationExpression x -> NotificationExpression
$cfrom :: forall x. NotificationExpression -> Rep NotificationExpression x
Generic, NotificationExpression -> ()
forall a. (a -> ()) -> NFData a
rnf :: NotificationExpression -> ()
$crnf :: NotificationExpression -> ()
NFData)
type TypeVarName = StringType
data TypeConstructorDef = ADTypeConstructorDef TypeConstructorName [TypeVarName] |
PrimitiveTypeConstructorDef TypeConstructorName AtomType
deriving (Int -> TypeConstructorDef -> ShowS
[TypeConstructorDef] -> ShowS
TypeConstructorDef -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TypeConstructorDef] -> ShowS
$cshowList :: [TypeConstructorDef] -> ShowS
show :: TypeConstructorDef -> String
$cshow :: TypeConstructorDef -> String
showsPrec :: Int -> TypeConstructorDef -> ShowS
$cshowsPrec :: Int -> TypeConstructorDef -> ShowS
Show, forall x. Rep TypeConstructorDef x -> TypeConstructorDef
forall x. TypeConstructorDef -> Rep TypeConstructorDef x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TypeConstructorDef x -> TypeConstructorDef
$cfrom :: forall x. TypeConstructorDef -> Rep TypeConstructorDef x
Generic, TypeConstructorDef -> TypeConstructorDef -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypeConstructorDef -> TypeConstructorDef -> Bool
$c/= :: TypeConstructorDef -> TypeConstructorDef -> Bool
== :: TypeConstructorDef -> TypeConstructorDef -> Bool
$c== :: TypeConstructorDef -> TypeConstructorDef -> Bool
Eq, TypeConstructorDef -> ()
forall a. (a -> ()) -> NFData a
rnf :: TypeConstructorDef -> ()
$crnf :: TypeConstructorDef -> ()
NFData, Eq TypeConstructorDef
Int -> TypeConstructorDef -> Int
TypeConstructorDef -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: TypeConstructorDef -> Int
$chash :: TypeConstructorDef -> Int
hashWithSalt :: Int -> TypeConstructorDef -> Int
$chashWithSalt :: Int -> TypeConstructorDef -> Int
Hashable, ReadPrec [TypeConstructorDef]
ReadPrec TypeConstructorDef
Int -> ReadS TypeConstructorDef
ReadS [TypeConstructorDef]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TypeConstructorDef]
$creadListPrec :: ReadPrec [TypeConstructorDef]
readPrec :: ReadPrec TypeConstructorDef
$creadPrec :: ReadPrec TypeConstructorDef
readList :: ReadS [TypeConstructorDef]
$creadList :: ReadS [TypeConstructorDef]
readsPrec :: Int -> ReadS TypeConstructorDef
$creadsPrec :: Int -> ReadS TypeConstructorDef
Read)
type TypeConstructor = TypeConstructorBase ()
data TypeConstructorBase a = ADTypeConstructor TypeConstructorName [TypeConstructor] |
PrimitiveTypeConstructor TypeConstructorName AtomType |
RelationAtomTypeConstructor [AttributeExprBase a] |
TypeVariable TypeVarName
deriving (Int -> TypeConstructorBase a -> ShowS
forall a. Show a => Int -> TypeConstructorBase a -> ShowS
forall a. Show a => [TypeConstructorBase a] -> ShowS
forall a. Show a => TypeConstructorBase a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TypeConstructorBase a] -> ShowS
$cshowList :: forall a. Show a => [TypeConstructorBase a] -> ShowS
show :: TypeConstructorBase a -> String
$cshow :: forall a. Show a => TypeConstructorBase a -> String
showsPrec :: Int -> TypeConstructorBase a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> TypeConstructorBase a -> ShowS
Show, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (TypeConstructorBase a) x -> TypeConstructorBase a
forall a x. TypeConstructorBase a -> Rep (TypeConstructorBase a) x
$cto :: forall a x. Rep (TypeConstructorBase a) x -> TypeConstructorBase a
$cfrom :: forall a x. TypeConstructorBase a -> Rep (TypeConstructorBase a) x
Generic, TypeConstructorBase a -> TypeConstructorBase a -> Bool
forall a.
Eq a =>
TypeConstructorBase a -> TypeConstructorBase a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypeConstructorBase a -> TypeConstructorBase a -> Bool
$c/= :: forall a.
Eq a =>
TypeConstructorBase a -> TypeConstructorBase a -> Bool
== :: TypeConstructorBase a -> TypeConstructorBase a -> Bool
$c== :: forall a.
Eq a =>
TypeConstructorBase a -> TypeConstructorBase a -> Bool
Eq, forall a. NFData a => TypeConstructorBase a -> ()
forall a. (a -> ()) -> NFData a
rnf :: TypeConstructorBase a -> ()
$crnf :: forall a. NFData a => TypeConstructorBase a -> ()
NFData, forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
forall {a}. Hashable a => Eq (TypeConstructorBase a)
forall a. Hashable a => Int -> TypeConstructorBase a -> Int
forall a. Hashable a => TypeConstructorBase a -> Int
hash :: TypeConstructorBase a -> Int
$chash :: forall a. Hashable a => TypeConstructorBase a -> Int
hashWithSalt :: Int -> TypeConstructorBase a -> Int
$chashWithSalt :: forall a. Hashable a => Int -> TypeConstructorBase a -> Int
Hashable, ReadPrec [TypeConstructorBase a]
ReadPrec (TypeConstructorBase a)
ReadS [TypeConstructorBase a]
forall a. Read a => ReadPrec [TypeConstructorBase a]
forall a. Read a => ReadPrec (TypeConstructorBase a)
forall a. Read a => Int -> ReadS (TypeConstructorBase a)
forall a. Read a => ReadS [TypeConstructorBase a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TypeConstructorBase a]
$creadListPrec :: forall a. Read a => ReadPrec [TypeConstructorBase a]
readPrec :: ReadPrec (TypeConstructorBase a)
$creadPrec :: forall a. Read a => ReadPrec (TypeConstructorBase a)
readList :: ReadS [TypeConstructorBase a]
$creadList :: forall a. Read a => ReadS [TypeConstructorBase a]
readsPrec :: Int -> ReadS (TypeConstructorBase a)
$creadsPrec :: forall a. Read a => Int -> ReadS (TypeConstructorBase a)
Read)
type TypeConstructorMapping = [(TypeConstructorDef, DataConstructorDefs)]
type TypeConstructorName = StringType
type TypeConstructorArgName = StringType
type DataConstructorName = StringType
type AtomTypeName = StringType
data DataConstructorDef = DataConstructorDef DataConstructorName [DataConstructorDefArg] deriving (DataConstructorDef -> DataConstructorDef -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DataConstructorDef -> DataConstructorDef -> Bool
$c/= :: DataConstructorDef -> DataConstructorDef -> Bool
== :: DataConstructorDef -> DataConstructorDef -> Bool
$c== :: DataConstructorDef -> DataConstructorDef -> Bool
Eq, Int -> DataConstructorDef -> ShowS
DataConstructorDefs -> ShowS
DataConstructorDef -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: DataConstructorDefs -> ShowS
$cshowList :: DataConstructorDefs -> ShowS
show :: DataConstructorDef -> String
$cshow :: DataConstructorDef -> String
showsPrec :: Int -> DataConstructorDef -> ShowS
$cshowsPrec :: Int -> DataConstructorDef -> ShowS
Show, forall x. Rep DataConstructorDef x -> DataConstructorDef
forall x. DataConstructorDef -> Rep DataConstructorDef x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DataConstructorDef x -> DataConstructorDef
$cfrom :: forall x. DataConstructorDef -> Rep DataConstructorDef x
Generic, DataConstructorDef -> ()
forall a. (a -> ()) -> NFData a
rnf :: DataConstructorDef -> ()
$crnf :: DataConstructorDef -> ()
NFData, Eq DataConstructorDef
Int -> DataConstructorDef -> Int
DataConstructorDef -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: DataConstructorDef -> Int
$chash :: DataConstructorDef -> Int
hashWithSalt :: Int -> DataConstructorDef -> Int
$chashWithSalt :: Int -> DataConstructorDef -> Int
Hashable, ReadPrec DataConstructorDefs
ReadPrec DataConstructorDef
Int -> ReadS DataConstructorDef
ReadS DataConstructorDefs
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec DataConstructorDefs
$creadListPrec :: ReadPrec DataConstructorDefs
readPrec :: ReadPrec DataConstructorDef
$creadPrec :: ReadPrec DataConstructorDef
readList :: ReadS DataConstructorDefs
$creadList :: ReadS DataConstructorDefs
readsPrec :: Int -> ReadS DataConstructorDef
$creadsPrec :: Int -> ReadS DataConstructorDef
Read)
type DataConstructorDefs = [DataConstructorDef]
data DataConstructorDefArg = DataConstructorDefTypeConstructorArg TypeConstructor |
DataConstructorDefTypeVarNameArg TypeVarName
deriving (Int -> DataConstructorDefArg -> ShowS
[DataConstructorDefArg] -> ShowS
DataConstructorDefArg -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DataConstructorDefArg] -> ShowS
$cshowList :: [DataConstructorDefArg] -> ShowS
show :: DataConstructorDefArg -> String
$cshow :: DataConstructorDefArg -> String
showsPrec :: Int -> DataConstructorDefArg -> ShowS
$cshowsPrec :: Int -> DataConstructorDefArg -> ShowS
Show, forall x. Rep DataConstructorDefArg x -> DataConstructorDefArg
forall x. DataConstructorDefArg -> Rep DataConstructorDefArg x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DataConstructorDefArg x -> DataConstructorDefArg
$cfrom :: forall x. DataConstructorDefArg -> Rep DataConstructorDefArg x
Generic, DataConstructorDefArg -> DataConstructorDefArg -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DataConstructorDefArg -> DataConstructorDefArg -> Bool
$c/= :: DataConstructorDefArg -> DataConstructorDefArg -> Bool
== :: DataConstructorDefArg -> DataConstructorDefArg -> Bool
$c== :: DataConstructorDefArg -> DataConstructorDefArg -> Bool
Eq, DataConstructorDefArg -> ()
forall a. (a -> ()) -> NFData a
rnf :: DataConstructorDefArg -> ()
$crnf :: DataConstructorDefArg -> ()
NFData, Eq DataConstructorDefArg
Int -> DataConstructorDefArg -> Int
DataConstructorDefArg -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: DataConstructorDefArg -> Int
$chash :: DataConstructorDefArg -> Int
hashWithSalt :: Int -> DataConstructorDefArg -> Int
$chashWithSalt :: Int -> DataConstructorDefArg -> Int
Hashable, ReadPrec [DataConstructorDefArg]
ReadPrec DataConstructorDefArg
Int -> ReadS DataConstructorDefArg
ReadS [DataConstructorDefArg]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DataConstructorDefArg]
$creadListPrec :: ReadPrec [DataConstructorDefArg]
readPrec :: ReadPrec DataConstructorDefArg
$creadPrec :: ReadPrec DataConstructorDefArg
readList :: ReadS [DataConstructorDefArg]
$creadList :: ReadS [DataConstructorDefArg]
readsPrec :: Int -> ReadS DataConstructorDefArg
$creadsPrec :: Int -> ReadS DataConstructorDefArg
Read)
type InclusionDependencies = M.Map IncDepName InclusionDependency
type RelationVariables = M.Map RelVarName GraphRefRelationalExpr
data GraphRefTransactionMarker = TransactionMarker TransactionId |
UncommittedContextMarker
deriving (GraphRefTransactionMarker -> GraphRefTransactionMarker -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GraphRefTransactionMarker -> GraphRefTransactionMarker -> Bool
$c/= :: GraphRefTransactionMarker -> GraphRefTransactionMarker -> Bool
== :: GraphRefTransactionMarker -> GraphRefTransactionMarker -> Bool
$c== :: GraphRefTransactionMarker -> GraphRefTransactionMarker -> Bool
Eq, Int -> GraphRefTransactionMarker -> ShowS
[GraphRefTransactionMarker] -> ShowS
GraphRefTransactionMarker -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GraphRefTransactionMarker] -> ShowS
$cshowList :: [GraphRefTransactionMarker] -> ShowS
show :: GraphRefTransactionMarker -> String
$cshow :: GraphRefTransactionMarker -> String
showsPrec :: Int -> GraphRefTransactionMarker -> ShowS
$cshowsPrec :: Int -> GraphRefTransactionMarker -> ShowS
Show, forall x.
Rep GraphRefTransactionMarker x -> GraphRefTransactionMarker
forall x.
GraphRefTransactionMarker -> Rep GraphRefTransactionMarker x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GraphRefTransactionMarker x -> GraphRefTransactionMarker
$cfrom :: forall x.
GraphRefTransactionMarker -> Rep GraphRefTransactionMarker x
Generic, GraphRefTransactionMarker -> ()
forall a. (a -> ()) -> NFData a
rnf :: GraphRefTransactionMarker -> ()
$crnf :: GraphRefTransactionMarker -> ()
NFData, Eq GraphRefTransactionMarker
GraphRefTransactionMarker -> GraphRefTransactionMarker -> Bool
GraphRefTransactionMarker -> GraphRefTransactionMarker -> Ordering
GraphRefTransactionMarker
-> GraphRefTransactionMarker -> GraphRefTransactionMarker
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 :: GraphRefTransactionMarker
-> GraphRefTransactionMarker -> GraphRefTransactionMarker
$cmin :: GraphRefTransactionMarker
-> GraphRefTransactionMarker -> GraphRefTransactionMarker
max :: GraphRefTransactionMarker
-> GraphRefTransactionMarker -> GraphRefTransactionMarker
$cmax :: GraphRefTransactionMarker
-> GraphRefTransactionMarker -> GraphRefTransactionMarker
>= :: GraphRefTransactionMarker -> GraphRefTransactionMarker -> Bool
$c>= :: GraphRefTransactionMarker -> GraphRefTransactionMarker -> Bool
> :: GraphRefTransactionMarker -> GraphRefTransactionMarker -> Bool
$c> :: GraphRefTransactionMarker -> GraphRefTransactionMarker -> Bool
<= :: GraphRefTransactionMarker -> GraphRefTransactionMarker -> Bool
$c<= :: GraphRefTransactionMarker -> GraphRefTransactionMarker -> Bool
< :: GraphRefTransactionMarker -> GraphRefTransactionMarker -> Bool
$c< :: GraphRefTransactionMarker -> GraphRefTransactionMarker -> Bool
compare :: GraphRefTransactionMarker -> GraphRefTransactionMarker -> Ordering
$ccompare :: GraphRefTransactionMarker -> GraphRefTransactionMarker -> Ordering
Ord)
type GraphRefRelationalExpr = RelationalExprBase GraphRefTransactionMarker
type SchemaName = StringType
type Subschemas = M.Map SchemaName Schema
data Schemas = Schemas DatabaseContext Subschemas
deriving (forall x. Rep Schemas x -> Schemas
forall x. Schemas -> Rep Schemas x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Schemas x -> Schemas
$cfrom :: forall x. Schemas -> Rep Schemas x
Generic)
newtype Schema = Schema SchemaIsomorphs
deriving (forall x. Rep Schema x -> Schema
forall x. Schema -> Rep Schema x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Schema x -> Schema
$cfrom :: forall x. Schema -> Rep Schema x
Generic)
data SchemaIsomorph = IsoRestrict RelVarName RestrictionPredicateExpr (RelVarName, RelVarName) |
IsoRename RelVarName RelVarName |
IsoUnion (RelVarName, RelVarName) RestrictionPredicateExpr RelVarName
deriving (forall x. Rep SchemaIsomorph x -> SchemaIsomorph
forall x. SchemaIsomorph -> Rep SchemaIsomorph x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SchemaIsomorph x -> SchemaIsomorph
$cfrom :: forall x. SchemaIsomorph -> Rep SchemaIsomorph x
Generic, Int -> SchemaIsomorph -> ShowS
[SchemaIsomorph] -> ShowS
SchemaIsomorph -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SchemaIsomorph] -> ShowS
$cshowList :: [SchemaIsomorph] -> ShowS
show :: SchemaIsomorph -> String
$cshow :: SchemaIsomorph -> String
showsPrec :: Int -> SchemaIsomorph -> ShowS
$cshowsPrec :: Int -> SchemaIsomorph -> ShowS
Show)
type SchemaIsomorphs = [SchemaIsomorph]
type RegisteredQueryName = StringType
type RegisteredQueries = M.Map RegisteredQueryName RelationalExpr
data DatabaseContext = DatabaseContext {
DatabaseContext -> InclusionDependencies
inclusionDependencies :: InclusionDependencies,
DatabaseContext -> RelationVariables
relationVariables :: RelationVariables,
DatabaseContext -> AtomFunctions
atomFunctions :: AtomFunctions,
DatabaseContext -> DatabaseContextFunctions
dbcFunctions :: DatabaseContextFunctions,
DatabaseContext -> Notifications
notifications :: Notifications,
DatabaseContext -> TypeConstructorMapping
typeConstructorMapping :: TypeConstructorMapping,
DatabaseContext -> RegisteredQueries
registeredQueries :: RegisteredQueries
} deriving (DatabaseContext -> ()
forall a. (a -> ()) -> NFData a
rnf :: DatabaseContext -> ()
$crnf :: DatabaseContext -> ()
NFData, forall x. Rep DatabaseContext x -> DatabaseContext
forall x. DatabaseContext -> Rep DatabaseContext x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DatabaseContext x -> DatabaseContext
$cfrom :: forall x. DatabaseContext -> Rep DatabaseContext x
Generic)
type IncDepName = StringType
data InclusionDependency = InclusionDependency RelationalExpr RelationalExpr deriving (Int -> InclusionDependency -> ShowS
[InclusionDependency] -> ShowS
InclusionDependency -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InclusionDependency] -> ShowS
$cshowList :: [InclusionDependency] -> ShowS
show :: InclusionDependency -> String
$cshow :: InclusionDependency -> String
showsPrec :: Int -> InclusionDependency -> ShowS
$cshowsPrec :: Int -> InclusionDependency -> ShowS
Show, InclusionDependency -> InclusionDependency -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InclusionDependency -> InclusionDependency -> Bool
$c/= :: InclusionDependency -> InclusionDependency -> Bool
== :: InclusionDependency -> InclusionDependency -> Bool
$c== :: InclusionDependency -> InclusionDependency -> Bool
Eq, forall x. Rep InclusionDependency x -> InclusionDependency
forall x. InclusionDependency -> Rep InclusionDependency x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InclusionDependency x -> InclusionDependency
$cfrom :: forall x. InclusionDependency -> Rep InclusionDependency x
Generic, InclusionDependency -> ()
forall a. (a -> ()) -> NFData a
rnf :: InclusionDependency -> ()
$crnf :: InclusionDependency -> ()
NFData, Eq InclusionDependency
Int -> InclusionDependency -> Int
InclusionDependency -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: InclusionDependency -> Int
$chash :: InclusionDependency -> Int
hashWithSalt :: Int -> InclusionDependency -> Int
$chashWithSalt :: Int -> InclusionDependency -> Int
Hashable, ReadPrec [InclusionDependency]
ReadPrec InclusionDependency
Int -> ReadS InclusionDependency
ReadS [InclusionDependency]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [InclusionDependency]
$creadListPrec :: ReadPrec [InclusionDependency]
readPrec :: ReadPrec InclusionDependency
$creadPrec :: ReadPrec InclusionDependency
readList :: ReadS [InclusionDependency]
$creadList :: ReadS [InclusionDependency]
readsPrec :: Int -> ReadS InclusionDependency
$creadsPrec :: Int -> ReadS InclusionDependency
Read)
type AttributeNameAtomExprMap = M.Map AttributeName AtomExpr
type DatabaseContextExprName = StringType
type DatabaseContextExpr = DatabaseContextExprBase ()
instance Hashable DatabaseContextExpr
type GraphRefDatabaseContextExpr = DatabaseContextExprBase GraphRefTransactionMarker
data DatabaseContextExprBase a =
NoOperation |
Define RelVarName [AttributeExprBase a] |
Undefine RelVarName |
Assign RelVarName (RelationalExprBase a) |
Insert RelVarName (RelationalExprBase a) |
Delete RelVarName (RestrictionPredicateExprBase a) |
Update RelVarName AttributeNameAtomExprMap (RestrictionPredicateExprBase a) |
AddInclusionDependency IncDepName InclusionDependency |
RemoveInclusionDependency IncDepName |
AddNotification NotificationName RelationalExpr RelationalExpr RelationalExpr |
RemoveNotification NotificationName |
AddTypeConstructor TypeConstructorDef [DataConstructorDef] |
RemoveTypeConstructor TypeConstructorName |
RemoveAtomFunction FunctionName |
RemoveDatabaseContextFunction FunctionName |
ExecuteDatabaseContextFunction FunctionName [AtomExprBase a] |
AddRegisteredQuery RegisteredQueryName RelationalExpr |
RemoveRegisteredQuery RegisteredQueryName |
MultipleExpr [DatabaseContextExprBase a]
deriving (Int -> DatabaseContextExprBase a -> ShowS
forall a. Show a => Int -> DatabaseContextExprBase a -> ShowS
forall a. Show a => [DatabaseContextExprBase a] -> ShowS
forall a. Show a => DatabaseContextExprBase a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DatabaseContextExprBase a] -> ShowS
$cshowList :: forall a. Show a => [DatabaseContextExprBase a] -> ShowS
show :: DatabaseContextExprBase a -> String
$cshow :: forall a. Show a => DatabaseContextExprBase a -> String
showsPrec :: Int -> DatabaseContextExprBase a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> DatabaseContextExprBase a -> ShowS
Show, ReadPrec [DatabaseContextExprBase a]
ReadPrec (DatabaseContextExprBase a)
ReadS [DatabaseContextExprBase a]
forall a. Read a => ReadPrec [DatabaseContextExprBase a]
forall a. Read a => ReadPrec (DatabaseContextExprBase a)
forall a. Read a => Int -> ReadS (DatabaseContextExprBase a)
forall a. Read a => ReadS [DatabaseContextExprBase a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DatabaseContextExprBase a]
$creadListPrec :: forall a. Read a => ReadPrec [DatabaseContextExprBase a]
readPrec :: ReadPrec (DatabaseContextExprBase a)
$creadPrec :: forall a. Read a => ReadPrec (DatabaseContextExprBase a)
readList :: ReadS [DatabaseContextExprBase a]
$creadList :: forall a. Read a => ReadS [DatabaseContextExprBase a]
readsPrec :: Int -> ReadS (DatabaseContextExprBase a)
$creadsPrec :: forall a. Read a => Int -> ReadS (DatabaseContextExprBase a)
Read, DatabaseContextExprBase a -> DatabaseContextExprBase a -> Bool
forall a.
Eq a =>
DatabaseContextExprBase a -> DatabaseContextExprBase a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DatabaseContextExprBase a -> DatabaseContextExprBase a -> Bool
$c/= :: forall a.
Eq a =>
DatabaseContextExprBase a -> DatabaseContextExprBase a -> Bool
== :: DatabaseContextExprBase a -> DatabaseContextExprBase a -> Bool
$c== :: forall a.
Eq a =>
DatabaseContextExprBase a -> DatabaseContextExprBase a -> Bool
Eq, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x.
Rep (DatabaseContextExprBase a) x -> DatabaseContextExprBase a
forall a x.
DatabaseContextExprBase a -> Rep (DatabaseContextExprBase a) x
$cto :: forall a x.
Rep (DatabaseContextExprBase a) x -> DatabaseContextExprBase a
$cfrom :: forall a x.
DatabaseContextExprBase a -> Rep (DatabaseContextExprBase a) x
Generic, forall a. NFData a => DatabaseContextExprBase a -> ()
forall a. (a -> ()) -> NFData a
rnf :: DatabaseContextExprBase a -> ()
$crnf :: forall a. NFData a => DatabaseContextExprBase a -> ()
NFData)
type ObjModuleName = StringType
type ObjFunctionName = StringType
type Range = (Int,Int)
data DatabaseContextIOExprBase a =
AddAtomFunction FunctionName [TypeConstructor] FunctionBodyScript |
LoadAtomFunctions ObjModuleName ObjFunctionName FilePath |
AddDatabaseContextFunction FunctionName [TypeConstructor] FunctionBodyScript |
LoadDatabaseContextFunctions ObjModuleName ObjFunctionName FilePath |
CreateArbitraryRelation RelVarName [AttributeExprBase a] Range
deriving (Int -> DatabaseContextIOExprBase a -> ShowS
forall a. Show a => Int -> DatabaseContextIOExprBase a -> ShowS
forall a. Show a => [DatabaseContextIOExprBase a] -> ShowS
forall a. Show a => DatabaseContextIOExprBase a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DatabaseContextIOExprBase a] -> ShowS
$cshowList :: forall a. Show a => [DatabaseContextIOExprBase a] -> ShowS
show :: DatabaseContextIOExprBase a -> String
$cshow :: forall a. Show a => DatabaseContextIOExprBase a -> String
showsPrec :: Int -> DatabaseContextIOExprBase a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> DatabaseContextIOExprBase a -> ShowS
Show, DatabaseContextIOExprBase a -> DatabaseContextIOExprBase a -> Bool
forall a.
Eq a =>
DatabaseContextIOExprBase a -> DatabaseContextIOExprBase a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DatabaseContextIOExprBase a -> DatabaseContextIOExprBase a -> Bool
$c/= :: forall a.
Eq a =>
DatabaseContextIOExprBase a -> DatabaseContextIOExprBase a -> Bool
== :: DatabaseContextIOExprBase a -> DatabaseContextIOExprBase a -> Bool
$c== :: forall a.
Eq a =>
DatabaseContextIOExprBase a -> DatabaseContextIOExprBase a -> Bool
Eq, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x.
Rep (DatabaseContextIOExprBase a) x -> DatabaseContextIOExprBase a
forall a x.
DatabaseContextIOExprBase a -> Rep (DatabaseContextIOExprBase a) x
$cto :: forall a x.
Rep (DatabaseContextIOExprBase a) x -> DatabaseContextIOExprBase a
$cfrom :: forall a x.
DatabaseContextIOExprBase a -> Rep (DatabaseContextIOExprBase a) x
Generic)
type GraphRefDatabaseContextIOExpr = DatabaseContextIOExprBase GraphRefTransactionMarker
type DatabaseContextIOExpr = DatabaseContextIOExprBase ()
type RestrictionPredicateExpr = RestrictionPredicateExprBase ()
instance Hashable RestrictionPredicateExpr
type GraphRefRestrictionPredicateExpr = RestrictionPredicateExprBase GraphRefTransactionMarker
data RestrictionPredicateExprBase a =
TruePredicate |
AndPredicate (RestrictionPredicateExprBase a) (RestrictionPredicateExprBase a) |
OrPredicate (RestrictionPredicateExprBase a) (RestrictionPredicateExprBase a) |
NotPredicate (RestrictionPredicateExprBase a) |
RelationalExprPredicate (RelationalExprBase a) |
AtomExprPredicate (AtomExprBase a) |
AttributeEqualityPredicate AttributeName (AtomExprBase a)
deriving (Int -> RestrictionPredicateExprBase a -> ShowS
forall a. Show a => Int -> RestrictionPredicateExprBase a -> ShowS
forall a. Show a => [RestrictionPredicateExprBase a] -> ShowS
forall a. Show a => RestrictionPredicateExprBase a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RestrictionPredicateExprBase a] -> ShowS
$cshowList :: forall a. Show a => [RestrictionPredicateExprBase a] -> ShowS
show :: RestrictionPredicateExprBase a -> String
$cshow :: forall a. Show a => RestrictionPredicateExprBase a -> String
showsPrec :: Int -> RestrictionPredicateExprBase a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> RestrictionPredicateExprBase a -> ShowS
Show, ReadPrec [RestrictionPredicateExprBase a]
ReadPrec (RestrictionPredicateExprBase a)
ReadS [RestrictionPredicateExprBase a]
forall a. Read a => ReadPrec [RestrictionPredicateExprBase a]
forall a. Read a => ReadPrec (RestrictionPredicateExprBase a)
forall a. Read a => Int -> ReadS (RestrictionPredicateExprBase a)
forall a. Read a => ReadS [RestrictionPredicateExprBase a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RestrictionPredicateExprBase a]
$creadListPrec :: forall a. Read a => ReadPrec [RestrictionPredicateExprBase a]
readPrec :: ReadPrec (RestrictionPredicateExprBase a)
$creadPrec :: forall a. Read a => ReadPrec (RestrictionPredicateExprBase a)
readList :: ReadS [RestrictionPredicateExprBase a]
$creadList :: forall a. Read a => ReadS [RestrictionPredicateExprBase a]
readsPrec :: Int -> ReadS (RestrictionPredicateExprBase a)
$creadsPrec :: forall a. Read a => Int -> ReadS (RestrictionPredicateExprBase a)
Read, RestrictionPredicateExprBase a
-> RestrictionPredicateExprBase a -> Bool
forall a.
Eq a =>
RestrictionPredicateExprBase a
-> RestrictionPredicateExprBase a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RestrictionPredicateExprBase a
-> RestrictionPredicateExprBase a -> Bool
$c/= :: forall a.
Eq a =>
RestrictionPredicateExprBase a
-> RestrictionPredicateExprBase a -> Bool
== :: RestrictionPredicateExprBase a
-> RestrictionPredicateExprBase a -> Bool
$c== :: forall a.
Eq a =>
RestrictionPredicateExprBase a
-> RestrictionPredicateExprBase a -> Bool
Eq, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x.
Rep (RestrictionPredicateExprBase a) x
-> RestrictionPredicateExprBase a
forall a x.
RestrictionPredicateExprBase a
-> Rep (RestrictionPredicateExprBase a) x
$cto :: forall a x.
Rep (RestrictionPredicateExprBase a) x
-> RestrictionPredicateExprBase a
$cfrom :: forall a x.
RestrictionPredicateExprBase a
-> Rep (RestrictionPredicateExprBase a) x
Generic, forall a. NFData a => RestrictionPredicateExprBase a -> ()
forall a. (a -> ()) -> NFData a
rnf :: RestrictionPredicateExprBase a -> ()
$crnf :: forall a. NFData a => RestrictionPredicateExprBase a -> ()
NFData, forall a. Eq a => a -> RestrictionPredicateExprBase a -> Bool
forall a. Num a => RestrictionPredicateExprBase a -> a
forall a. Ord a => RestrictionPredicateExprBase a -> a
forall m. Monoid m => RestrictionPredicateExprBase m -> m
forall a. RestrictionPredicateExprBase a -> Bool
forall a. RestrictionPredicateExprBase a -> Int
forall a. RestrictionPredicateExprBase a -> [a]
forall a. (a -> a -> a) -> RestrictionPredicateExprBase a -> a
forall m a.
Monoid m =>
(a -> m) -> RestrictionPredicateExprBase a -> m
forall b a.
(b -> a -> b) -> b -> RestrictionPredicateExprBase a -> b
forall a b.
(a -> b -> b) -> b -> RestrictionPredicateExprBase a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: forall a. Num a => RestrictionPredicateExprBase a -> a
$cproduct :: forall a. Num a => RestrictionPredicateExprBase a -> a
sum :: forall a. Num a => RestrictionPredicateExprBase a -> a
$csum :: forall a. Num a => RestrictionPredicateExprBase a -> a
minimum :: forall a. Ord a => RestrictionPredicateExprBase a -> a
$cminimum :: forall a. Ord a => RestrictionPredicateExprBase a -> a
maximum :: forall a. Ord a => RestrictionPredicateExprBase a -> a
$cmaximum :: forall a. Ord a => RestrictionPredicateExprBase a -> a
elem :: forall a. Eq a => a -> RestrictionPredicateExprBase a -> Bool
$celem :: forall a. Eq a => a -> RestrictionPredicateExprBase a -> Bool
length :: forall a. RestrictionPredicateExprBase a -> Int
$clength :: forall a. RestrictionPredicateExprBase a -> Int
null :: forall a. RestrictionPredicateExprBase a -> Bool
$cnull :: forall a. RestrictionPredicateExprBase a -> Bool
toList :: forall a. RestrictionPredicateExprBase a -> [a]
$ctoList :: forall a. RestrictionPredicateExprBase a -> [a]
foldl1 :: forall a. (a -> a -> a) -> RestrictionPredicateExprBase a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> RestrictionPredicateExprBase a -> a
foldr1 :: forall a. (a -> a -> a) -> RestrictionPredicateExprBase a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> RestrictionPredicateExprBase a -> a
foldl' :: forall b a.
(b -> a -> b) -> b -> RestrictionPredicateExprBase a -> b
$cfoldl' :: forall b a.
(b -> a -> b) -> b -> RestrictionPredicateExprBase a -> b
foldl :: forall b a.
(b -> a -> b) -> b -> RestrictionPredicateExprBase a -> b
$cfoldl :: forall b a.
(b -> a -> b) -> b -> RestrictionPredicateExprBase a -> b
foldr' :: forall a b.
(a -> b -> b) -> b -> RestrictionPredicateExprBase a -> b
$cfoldr' :: forall a b.
(a -> b -> b) -> b -> RestrictionPredicateExprBase a -> b
foldr :: forall a b.
(a -> b -> b) -> b -> RestrictionPredicateExprBase a -> b
$cfoldr :: forall a b.
(a -> b -> b) -> b -> RestrictionPredicateExprBase a -> b
foldMap' :: forall m a.
Monoid m =>
(a -> m) -> RestrictionPredicateExprBase a -> m
$cfoldMap' :: forall m a.
Monoid m =>
(a -> m) -> RestrictionPredicateExprBase a -> m
foldMap :: forall m a.
Monoid m =>
(a -> m) -> RestrictionPredicateExprBase a -> m
$cfoldMap :: forall m a.
Monoid m =>
(a -> m) -> RestrictionPredicateExprBase a -> m
fold :: forall m. Monoid m => RestrictionPredicateExprBase m -> m
$cfold :: forall m. Monoid m => RestrictionPredicateExprBase m -> m
Foldable, forall a b.
a
-> RestrictionPredicateExprBase b -> RestrictionPredicateExprBase a
forall a b.
(a -> b)
-> RestrictionPredicateExprBase a -> RestrictionPredicateExprBase b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b.
a
-> RestrictionPredicateExprBase b -> RestrictionPredicateExprBase a
$c<$ :: forall a b.
a
-> RestrictionPredicateExprBase b -> RestrictionPredicateExprBase a
fmap :: forall a b.
(a -> b)
-> RestrictionPredicateExprBase a -> RestrictionPredicateExprBase b
$cfmap :: forall a b.
(a -> b)
-> RestrictionPredicateExprBase a -> RestrictionPredicateExprBase b
Functor, Functor RestrictionPredicateExprBase
Foldable RestrictionPredicateExprBase
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
RestrictionPredicateExprBase (m a)
-> m (RestrictionPredicateExprBase a)
forall (f :: * -> *) a.
Applicative f =>
RestrictionPredicateExprBase (f a)
-> f (RestrictionPredicateExprBase a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> RestrictionPredicateExprBase a
-> m (RestrictionPredicateExprBase b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> RestrictionPredicateExprBase a
-> f (RestrictionPredicateExprBase b)
sequence :: forall (m :: * -> *) a.
Monad m =>
RestrictionPredicateExprBase (m a)
-> m (RestrictionPredicateExprBase a)
$csequence :: forall (m :: * -> *) a.
Monad m =>
RestrictionPredicateExprBase (m a)
-> m (RestrictionPredicateExprBase a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> RestrictionPredicateExprBase a
-> m (RestrictionPredicateExprBase b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b)
-> RestrictionPredicateExprBase a
-> m (RestrictionPredicateExprBase b)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
RestrictionPredicateExprBase (f a)
-> f (RestrictionPredicateExprBase a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
RestrictionPredicateExprBase (f a)
-> f (RestrictionPredicateExprBase a)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> RestrictionPredicateExprBase a
-> f (RestrictionPredicateExprBase b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b)
-> RestrictionPredicateExprBase a
-> f (RestrictionPredicateExprBase b)
Traversable)
type HeadName = StringType
type TransactionHeads = M.Map HeadName Transaction
data TransactionGraph = TransactionGraph TransactionHeads (S.Set Transaction)
deriving forall x. Rep TransactionGraph x -> TransactionGraph
forall x. TransactionGraph -> Rep TransactionGraph x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TransactionGraph x -> TransactionGraph
$cfrom :: forall x. TransactionGraph -> Rep TransactionGraph x
Generic
transactionHeadsForGraph :: TransactionGraph -> TransactionHeads
transactionHeadsForGraph :: TransactionGraph -> TransactionHeads
transactionHeadsForGraph (TransactionGraph TransactionHeads
hs Set Transaction
_) = TransactionHeads
hs
transactionsForGraph :: TransactionGraph -> S.Set Transaction
transactionsForGraph :: TransactionGraph -> Set Transaction
transactionsForGraph (TransactionGraph TransactionHeads
_ Set Transaction
ts) = Set Transaction
ts
transactionIdsForGraph :: TransactionGraph -> S.Set TransactionId
transactionIdsForGraph :: TransactionGraph -> Set UUID
transactionIdsForGraph = forall b a. Ord b => (a -> b) -> Set a -> Set b
S.map Transaction -> UUID
transactionId forall b c a. (b -> c) -> (a -> b) -> a -> c
. TransactionGraph -> Set Transaction
transactionsForGraph
data TransactionInfo = TransactionInfo {
TransactionInfo -> TransactionParents
parents :: TransactionParents,
TransactionInfo -> UTCTime
stamp :: UTCTime,
TransactionInfo -> MerkleHash
merkleHash :: MerkleHash
} deriving (Int -> TransactionInfo -> ShowS
[TransactionInfo] -> ShowS
TransactionInfo -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TransactionInfo] -> ShowS
$cshowList :: [TransactionInfo] -> ShowS
show :: TransactionInfo -> String
$cshow :: TransactionInfo -> String
showsPrec :: Int -> TransactionInfo -> ShowS
$cshowsPrec :: Int -> TransactionInfo -> ShowS
Show, forall x. Rep TransactionInfo x -> TransactionInfo
forall x. TransactionInfo -> Rep TransactionInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TransactionInfo x -> TransactionInfo
$cfrom :: forall x. TransactionInfo -> Rep TransactionInfo x
Generic)
type TransactionParents = NE.NonEmpty TransactionId
type TransactionId = UUID
data Transaction = Transaction TransactionId TransactionInfo Schemas
deriving forall x. Rep Transaction x -> Transaction
forall x. Transaction -> Rep Transaction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Transaction x -> Transaction
$cfrom :: forall x. Transaction -> Rep Transaction x
Generic
data DisconnectedTransaction = DisconnectedTransaction TransactionId Schemas DirtyFlag
type DirtyFlag = Bool
type TransactionDiffExpr = DatabaseContextExpr
transactionId :: Transaction -> TransactionId
transactionId :: Transaction -> UUID
transactionId (Transaction UUID
tid TransactionInfo
_ Schemas
_) = UUID
tid
transactionInfo :: Transaction -> TransactionInfo
transactionInfo :: Transaction -> TransactionInfo
transactionInfo (Transaction UUID
_ TransactionInfo
info Schemas
_) = TransactionInfo
info
instance Eq Transaction where
(Transaction UUID
uuidA TransactionInfo
_ Schemas
_) == :: Transaction -> Transaction -> Bool
== (Transaction UUID
uuidB TransactionInfo
_ Schemas
_) = UUID
uuidA forall a. Eq a => a -> a -> Bool
== UUID
uuidB
instance Ord Transaction where
compare :: Transaction -> Transaction -> Ordering
compare (Transaction UUID
uuidA TransactionInfo
_ Schemas
_) (Transaction UUID
uuidB TransactionInfo
_ Schemas
_) = forall a. Ord a => a -> a -> Ordering
compare UUID
uuidA UUID
uuidB
type AtomExpr = AtomExprBase ()
instance Hashable AtomExpr
type GraphRefAtomExpr = AtomExprBase GraphRefTransactionMarker
type AggAtomFuncExprInfo = (AttributeName, AttributeName)
data AtomExprBase a = AttributeAtomExpr AttributeName |
SubrelationAttributeAtomExpr AttributeName AttributeName |
NakedAtomExpr !Atom |
FunctionAtomExpr !FunctionName [AtomExprBase a] a |
RelationAtomExpr (RelationalExprBase a) |
IfThenAtomExpr (AtomExprBase a) (AtomExprBase a) (AtomExprBase a) |
ConstructedAtomExpr DataConstructorName [AtomExprBase a] a
deriving (AtomExprBase a -> AtomExprBase a -> Bool
forall a. Eq a => AtomExprBase a -> AtomExprBase a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AtomExprBase a -> AtomExprBase a -> Bool
$c/= :: forall a. Eq a => AtomExprBase a -> AtomExprBase a -> Bool
== :: AtomExprBase a -> AtomExprBase a -> Bool
$c== :: forall a. Eq a => AtomExprBase a -> AtomExprBase a -> Bool
Eq, Int -> AtomExprBase a -> ShowS
forall a. Show a => Int -> AtomExprBase a -> ShowS
forall a. Show a => [AtomExprBase a] -> ShowS
forall a. Show a => AtomExprBase a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AtomExprBase a] -> ShowS
$cshowList :: forall a. Show a => [AtomExprBase a] -> ShowS
show :: AtomExprBase a -> String
$cshow :: forall a. Show a => AtomExprBase a -> String
showsPrec :: Int -> AtomExprBase a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> AtomExprBase a -> ShowS
Show, ReadPrec [AtomExprBase a]
ReadPrec (AtomExprBase a)
ReadS [AtomExprBase a]
forall a. Read a => ReadPrec [AtomExprBase a]
forall a. Read a => ReadPrec (AtomExprBase a)
forall a. Read a => Int -> ReadS (AtomExprBase a)
forall a. Read a => ReadS [AtomExprBase a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AtomExprBase a]
$creadListPrec :: forall a. Read a => ReadPrec [AtomExprBase a]
readPrec :: ReadPrec (AtomExprBase a)
$creadPrec :: forall a. Read a => ReadPrec (AtomExprBase a)
readList :: ReadS [AtomExprBase a]
$creadList :: forall a. Read a => ReadS [AtomExprBase a]
readsPrec :: Int -> ReadS (AtomExprBase a)
$creadsPrec :: forall a. Read a => Int -> ReadS (AtomExprBase a)
Read, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (AtomExprBase a) x -> AtomExprBase a
forall a x. AtomExprBase a -> Rep (AtomExprBase a) x
$cto :: forall a x. Rep (AtomExprBase a) x -> AtomExprBase a
$cfrom :: forall a x. AtomExprBase a -> Rep (AtomExprBase a) x
Generic, forall a. NFData a => AtomExprBase a -> ()
forall a. (a -> ()) -> NFData a
rnf :: AtomExprBase a -> ()
$crnf :: forall a. NFData a => AtomExprBase a -> ()
NFData, forall a. Eq a => a -> AtomExprBase a -> Bool
forall a. Num a => AtomExprBase a -> a
forall a. Ord a => AtomExprBase a -> a
forall m. Monoid m => AtomExprBase m -> m
forall a. AtomExprBase a -> Bool
forall a. AtomExprBase a -> Int
forall a. AtomExprBase a -> [a]
forall a. (a -> a -> a) -> AtomExprBase a -> a
forall m a. Monoid m => (a -> m) -> AtomExprBase a -> m
forall b a. (b -> a -> b) -> b -> AtomExprBase a -> b
forall a b. (a -> b -> b) -> b -> AtomExprBase a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: forall a. Num a => AtomExprBase a -> a
$cproduct :: forall a. Num a => AtomExprBase a -> a
sum :: forall a. Num a => AtomExprBase a -> a
$csum :: forall a. Num a => AtomExprBase a -> a
minimum :: forall a. Ord a => AtomExprBase a -> a
$cminimum :: forall a. Ord a => AtomExprBase a -> a
maximum :: forall a. Ord a => AtomExprBase a -> a
$cmaximum :: forall a. Ord a => AtomExprBase a -> a
elem :: forall a. Eq a => a -> AtomExprBase a -> Bool
$celem :: forall a. Eq a => a -> AtomExprBase a -> Bool
length :: forall a. AtomExprBase a -> Int
$clength :: forall a. AtomExprBase a -> Int
null :: forall a. AtomExprBase a -> Bool
$cnull :: forall a. AtomExprBase a -> Bool
toList :: forall a. AtomExprBase a -> [a]
$ctoList :: forall a. AtomExprBase a -> [a]
foldl1 :: forall a. (a -> a -> a) -> AtomExprBase a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> AtomExprBase a -> a
foldr1 :: forall a. (a -> a -> a) -> AtomExprBase a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> AtomExprBase a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> AtomExprBase a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> AtomExprBase a -> b
foldl :: forall b a. (b -> a -> b) -> b -> AtomExprBase a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> AtomExprBase a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> AtomExprBase a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> AtomExprBase a -> b
foldr :: forall a b. (a -> b -> b) -> b -> AtomExprBase a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> AtomExprBase a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> AtomExprBase a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> AtomExprBase a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> AtomExprBase a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> AtomExprBase a -> m
fold :: forall m. Monoid m => AtomExprBase m -> m
$cfold :: forall m. Monoid m => AtomExprBase m -> m
Foldable, forall a b. a -> AtomExprBase b -> AtomExprBase a
forall a b. (a -> b) -> AtomExprBase a -> AtomExprBase b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> AtomExprBase b -> AtomExprBase a
$c<$ :: forall a b. a -> AtomExprBase b -> AtomExprBase a
fmap :: forall a b. (a -> b) -> AtomExprBase a -> AtomExprBase b
$cfmap :: forall a b. (a -> b) -> AtomExprBase a -> AtomExprBase b
Functor, Functor AtomExprBase
Foldable AtomExprBase
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
AtomExprBase (m a) -> m (AtomExprBase a)
forall (f :: * -> *) a.
Applicative f =>
AtomExprBase (f a) -> f (AtomExprBase a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> AtomExprBase a -> m (AtomExprBase b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> AtomExprBase a -> f (AtomExprBase b)
sequence :: forall (m :: * -> *) a.
Monad m =>
AtomExprBase (m a) -> m (AtomExprBase a)
$csequence :: forall (m :: * -> *) a.
Monad m =>
AtomExprBase (m a) -> m (AtomExprBase a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> AtomExprBase a -> m (AtomExprBase b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> AtomExprBase a -> m (AtomExprBase b)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
AtomExprBase (f a) -> f (AtomExprBase a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
AtomExprBase (f a) -> f (AtomExprBase a)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> AtomExprBase a -> f (AtomExprBase b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> AtomExprBase a -> f (AtomExprBase b)
Traversable)
data ExtendTupleExprBase a = AttributeExtendTupleExpr AttributeName (AtomExprBase a)
deriving (Int -> ExtendTupleExprBase a -> ShowS
forall a. Show a => Int -> ExtendTupleExprBase a -> ShowS
forall a. Show a => [ExtendTupleExprBase a] -> ShowS
forall a. Show a => ExtendTupleExprBase a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExtendTupleExprBase a] -> ShowS
$cshowList :: forall a. Show a => [ExtendTupleExprBase a] -> ShowS
show :: ExtendTupleExprBase a -> String
$cshow :: forall a. Show a => ExtendTupleExprBase a -> String
showsPrec :: Int -> ExtendTupleExprBase a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> ExtendTupleExprBase a -> ShowS
Show, ReadPrec [ExtendTupleExprBase a]
ReadPrec (ExtendTupleExprBase a)
ReadS [ExtendTupleExprBase a]
forall a. Read a => ReadPrec [ExtendTupleExprBase a]
forall a. Read a => ReadPrec (ExtendTupleExprBase a)
forall a. Read a => Int -> ReadS (ExtendTupleExprBase a)
forall a. Read a => ReadS [ExtendTupleExprBase a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ExtendTupleExprBase a]
$creadListPrec :: forall a. Read a => ReadPrec [ExtendTupleExprBase a]
readPrec :: ReadPrec (ExtendTupleExprBase a)
$creadPrec :: forall a. Read a => ReadPrec (ExtendTupleExprBase a)
readList :: ReadS [ExtendTupleExprBase a]
$creadList :: forall a. Read a => ReadS [ExtendTupleExprBase a]
readsPrec :: Int -> ReadS (ExtendTupleExprBase a)
$creadsPrec :: forall a. Read a => Int -> ReadS (ExtendTupleExprBase a)
Read, ExtendTupleExprBase a -> ExtendTupleExprBase a -> Bool
forall a.
Eq a =>
ExtendTupleExprBase a -> ExtendTupleExprBase a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExtendTupleExprBase a -> ExtendTupleExprBase a -> Bool
$c/= :: forall a.
Eq a =>
ExtendTupleExprBase a -> ExtendTupleExprBase a -> Bool
== :: ExtendTupleExprBase a -> ExtendTupleExprBase a -> Bool
$c== :: forall a.
Eq a =>
ExtendTupleExprBase a -> ExtendTupleExprBase a -> Bool
Eq, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (ExtendTupleExprBase a) x -> ExtendTupleExprBase a
forall a x. ExtendTupleExprBase a -> Rep (ExtendTupleExprBase a) x
$cto :: forall a x. Rep (ExtendTupleExprBase a) x -> ExtendTupleExprBase a
$cfrom :: forall a x. ExtendTupleExprBase a -> Rep (ExtendTupleExprBase a) x
Generic, forall a. NFData a => ExtendTupleExprBase a -> ()
forall a. (a -> ()) -> NFData a
rnf :: ExtendTupleExprBase a -> ()
$crnf :: forall a. NFData a => ExtendTupleExprBase a -> ()
NFData, forall a. Eq a => a -> ExtendTupleExprBase a -> Bool
forall a. Num a => ExtendTupleExprBase a -> a
forall a. Ord a => ExtendTupleExprBase a -> a
forall m. Monoid m => ExtendTupleExprBase m -> m
forall a. ExtendTupleExprBase a -> Bool
forall a. ExtendTupleExprBase a -> Int
forall a. ExtendTupleExprBase a -> [a]
forall a. (a -> a -> a) -> ExtendTupleExprBase a -> a
forall m a. Monoid m => (a -> m) -> ExtendTupleExprBase a -> m
forall b a. (b -> a -> b) -> b -> ExtendTupleExprBase a -> b
forall a b. (a -> b -> b) -> b -> ExtendTupleExprBase a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: forall a. Num a => ExtendTupleExprBase a -> a
$cproduct :: forall a. Num a => ExtendTupleExprBase a -> a
sum :: forall a. Num a => ExtendTupleExprBase a -> a
$csum :: forall a. Num a => ExtendTupleExprBase a -> a
minimum :: forall a. Ord a => ExtendTupleExprBase a -> a
$cminimum :: forall a. Ord a => ExtendTupleExprBase a -> a
maximum :: forall a. Ord a => ExtendTupleExprBase a -> a
$cmaximum :: forall a. Ord a => ExtendTupleExprBase a -> a
elem :: forall a. Eq a => a -> ExtendTupleExprBase a -> Bool
$celem :: forall a. Eq a => a -> ExtendTupleExprBase a -> Bool
length :: forall a. ExtendTupleExprBase a -> Int
$clength :: forall a. ExtendTupleExprBase a -> Int
null :: forall a. ExtendTupleExprBase a -> Bool
$cnull :: forall a. ExtendTupleExprBase a -> Bool
toList :: forall a. ExtendTupleExprBase a -> [a]
$ctoList :: forall a. ExtendTupleExprBase a -> [a]
foldl1 :: forall a. (a -> a -> a) -> ExtendTupleExprBase a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> ExtendTupleExprBase a -> a
foldr1 :: forall a. (a -> a -> a) -> ExtendTupleExprBase a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> ExtendTupleExprBase a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> ExtendTupleExprBase a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> ExtendTupleExprBase a -> b
foldl :: forall b a. (b -> a -> b) -> b -> ExtendTupleExprBase a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> ExtendTupleExprBase a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> ExtendTupleExprBase a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> ExtendTupleExprBase a -> b
foldr :: forall a b. (a -> b -> b) -> b -> ExtendTupleExprBase a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> ExtendTupleExprBase a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> ExtendTupleExprBase a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> ExtendTupleExprBase a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> ExtendTupleExprBase a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> ExtendTupleExprBase a -> m
fold :: forall m. Monoid m => ExtendTupleExprBase m -> m
$cfold :: forall m. Monoid m => ExtendTupleExprBase m -> m
Foldable, forall a b. a -> ExtendTupleExprBase b -> ExtendTupleExprBase a
forall a b.
(a -> b) -> ExtendTupleExprBase a -> ExtendTupleExprBase b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> ExtendTupleExprBase b -> ExtendTupleExprBase a
$c<$ :: forall a b. a -> ExtendTupleExprBase b -> ExtendTupleExprBase a
fmap :: forall a b.
(a -> b) -> ExtendTupleExprBase a -> ExtendTupleExprBase b
$cfmap :: forall a b.
(a -> b) -> ExtendTupleExprBase a -> ExtendTupleExprBase b
Functor, Functor ExtendTupleExprBase
Foldable ExtendTupleExprBase
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
ExtendTupleExprBase (m a) -> m (ExtendTupleExprBase a)
forall (f :: * -> *) a.
Applicative f =>
ExtendTupleExprBase (f a) -> f (ExtendTupleExprBase a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> ExtendTupleExprBase a -> m (ExtendTupleExprBase b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> ExtendTupleExprBase a -> f (ExtendTupleExprBase b)
sequence :: forall (m :: * -> *) a.
Monad m =>
ExtendTupleExprBase (m a) -> m (ExtendTupleExprBase a)
$csequence :: forall (m :: * -> *) a.
Monad m =>
ExtendTupleExprBase (m a) -> m (ExtendTupleExprBase a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> ExtendTupleExprBase a -> m (ExtendTupleExprBase b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> ExtendTupleExprBase a -> m (ExtendTupleExprBase b)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
ExtendTupleExprBase (f a) -> f (ExtendTupleExprBase a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
ExtendTupleExprBase (f a) -> f (ExtendTupleExprBase a)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> ExtendTupleExprBase a -> f (ExtendTupleExprBase b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> ExtendTupleExprBase a -> f (ExtendTupleExprBase b)
Traversable)
type ExtendTupleExpr = ExtendTupleExprBase ()
instance Hashable ExtendTupleExpr
type GraphRefExtendTupleExpr = ExtendTupleExprBase GraphRefTransactionMarker
type AtomFunctions = HS.HashSet AtomFunction
type AtomFunctionBodyType = [Atom] -> Either AtomFunctionError Atom
type ObjectFileEntryFunctionName = String
type ObjectFilePath = FilePath
type ObjectModuleName = String
data AttributeNamesBase a = AttributeNames (S.Set AttributeName) |
InvertedAttributeNames (S.Set AttributeName) |
UnionAttributeNames (AttributeNamesBase a) (AttributeNamesBase a) |
IntersectAttributeNames (AttributeNamesBase a) (AttributeNamesBase a) |
RelationalExprAttributeNames (RelationalExprBase a)
deriving (AttributeNamesBase a -> AttributeNamesBase a -> Bool
forall a.
Eq a =>
AttributeNamesBase a -> AttributeNamesBase a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AttributeNamesBase a -> AttributeNamesBase a -> Bool
$c/= :: forall a.
Eq a =>
AttributeNamesBase a -> AttributeNamesBase a -> Bool
== :: AttributeNamesBase a -> AttributeNamesBase a -> Bool
$c== :: forall a.
Eq a =>
AttributeNamesBase a -> AttributeNamesBase a -> Bool
Eq, Int -> AttributeNamesBase a -> ShowS
forall a. Show a => Int -> AttributeNamesBase a -> ShowS
forall a. Show a => [AttributeNamesBase a] -> ShowS
forall a. Show a => AttributeNamesBase a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AttributeNamesBase a] -> ShowS
$cshowList :: forall a. Show a => [AttributeNamesBase a] -> ShowS
show :: AttributeNamesBase a -> String
$cshow :: forall a. Show a => AttributeNamesBase a -> String
showsPrec :: Int -> AttributeNamesBase a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> AttributeNamesBase a -> ShowS
Show, ReadPrec [AttributeNamesBase a]
ReadPrec (AttributeNamesBase a)
ReadS [AttributeNamesBase a]
forall a. Read a => ReadPrec [AttributeNamesBase a]
forall a. Read a => ReadPrec (AttributeNamesBase a)
forall a. Read a => Int -> ReadS (AttributeNamesBase a)
forall a. Read a => ReadS [AttributeNamesBase a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AttributeNamesBase a]
$creadListPrec :: forall a. Read a => ReadPrec [AttributeNamesBase a]
readPrec :: ReadPrec (AttributeNamesBase a)
$creadPrec :: forall a. Read a => ReadPrec (AttributeNamesBase a)
readList :: ReadS [AttributeNamesBase a]
$creadList :: forall a. Read a => ReadS [AttributeNamesBase a]
readsPrec :: Int -> ReadS (AttributeNamesBase a)
$creadsPrec :: forall a. Read a => Int -> ReadS (AttributeNamesBase a)
Read, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (AttributeNamesBase a) x -> AttributeNamesBase a
forall a x. AttributeNamesBase a -> Rep (AttributeNamesBase a) x
$cto :: forall a x. Rep (AttributeNamesBase a) x -> AttributeNamesBase a
$cfrom :: forall a x. AttributeNamesBase a -> Rep (AttributeNamesBase a) x
Generic, forall a. NFData a => AttributeNamesBase a -> ()
forall a. (a -> ()) -> NFData a
rnf :: AttributeNamesBase a -> ()
$crnf :: forall a. NFData a => AttributeNamesBase a -> ()
NFData, forall a. Eq a => a -> AttributeNamesBase a -> Bool
forall a. Num a => AttributeNamesBase a -> a
forall a. Ord a => AttributeNamesBase a -> a
forall m. Monoid m => AttributeNamesBase m -> m
forall a. AttributeNamesBase a -> Bool
forall a. AttributeNamesBase a -> Int
forall a. AttributeNamesBase a -> [a]
forall a. (a -> a -> a) -> AttributeNamesBase a -> a
forall m a. Monoid m => (a -> m) -> AttributeNamesBase a -> m
forall b a. (b -> a -> b) -> b -> AttributeNamesBase a -> b
forall a b. (a -> b -> b) -> b -> AttributeNamesBase a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: forall a. Num a => AttributeNamesBase a -> a
$cproduct :: forall a. Num a => AttributeNamesBase a -> a
sum :: forall a. Num a => AttributeNamesBase a -> a
$csum :: forall a. Num a => AttributeNamesBase a -> a
minimum :: forall a. Ord a => AttributeNamesBase a -> a
$cminimum :: forall a. Ord a => AttributeNamesBase a -> a
maximum :: forall a. Ord a => AttributeNamesBase a -> a
$cmaximum :: forall a. Ord a => AttributeNamesBase a -> a
elem :: forall a. Eq a => a -> AttributeNamesBase a -> Bool
$celem :: forall a. Eq a => a -> AttributeNamesBase a -> Bool
length :: forall a. AttributeNamesBase a -> Int
$clength :: forall a. AttributeNamesBase a -> Int
null :: forall a. AttributeNamesBase a -> Bool
$cnull :: forall a. AttributeNamesBase a -> Bool
toList :: forall a. AttributeNamesBase a -> [a]
$ctoList :: forall a. AttributeNamesBase a -> [a]
foldl1 :: forall a. (a -> a -> a) -> AttributeNamesBase a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> AttributeNamesBase a -> a
foldr1 :: forall a. (a -> a -> a) -> AttributeNamesBase a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> AttributeNamesBase a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> AttributeNamesBase a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> AttributeNamesBase a -> b
foldl :: forall b a. (b -> a -> b) -> b -> AttributeNamesBase a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> AttributeNamesBase a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> AttributeNamesBase a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> AttributeNamesBase a -> b
foldr :: forall a b. (a -> b -> b) -> b -> AttributeNamesBase a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> AttributeNamesBase a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> AttributeNamesBase a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> AttributeNamesBase a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> AttributeNamesBase a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> AttributeNamesBase a -> m
fold :: forall m. Monoid m => AttributeNamesBase m -> m
$cfold :: forall m. Monoid m => AttributeNamesBase m -> m
Foldable, forall a b. a -> AttributeNamesBase b -> AttributeNamesBase a
forall a b.
(a -> b) -> AttributeNamesBase a -> AttributeNamesBase b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> AttributeNamesBase b -> AttributeNamesBase a
$c<$ :: forall a b. a -> AttributeNamesBase b -> AttributeNamesBase a
fmap :: forall a b.
(a -> b) -> AttributeNamesBase a -> AttributeNamesBase b
$cfmap :: forall a b.
(a -> b) -> AttributeNamesBase a -> AttributeNamesBase b
Functor, Functor AttributeNamesBase
Foldable AttributeNamesBase
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
AttributeNamesBase (m a) -> m (AttributeNamesBase a)
forall (f :: * -> *) a.
Applicative f =>
AttributeNamesBase (f a) -> f (AttributeNamesBase a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> AttributeNamesBase a -> m (AttributeNamesBase b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> AttributeNamesBase a -> f (AttributeNamesBase b)
sequence :: forall (m :: * -> *) a.
Monad m =>
AttributeNamesBase (m a) -> m (AttributeNamesBase a)
$csequence :: forall (m :: * -> *) a.
Monad m =>
AttributeNamesBase (m a) -> m (AttributeNamesBase a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> AttributeNamesBase a -> m (AttributeNamesBase b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> AttributeNamesBase a -> m (AttributeNamesBase b)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
AttributeNamesBase (f a) -> f (AttributeNamesBase a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
AttributeNamesBase (f a) -> f (AttributeNamesBase a)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> AttributeNamesBase a -> f (AttributeNamesBase b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> AttributeNamesBase a -> f (AttributeNamesBase b)
Traversable)
type AttributeNames = AttributeNamesBase ()
instance Hashable AttributeNames
type GraphRefAttributeNames = AttributeNamesBase GraphRefTransactionMarker
data PersistenceStrategy = NoPersistence |
MinimalPersistence FilePath |
CrashSafePersistence FilePath
deriving (Int -> PersistenceStrategy -> ShowS
[PersistenceStrategy] -> ShowS
PersistenceStrategy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PersistenceStrategy] -> ShowS
$cshowList :: [PersistenceStrategy] -> ShowS
show :: PersistenceStrategy -> String
$cshow :: PersistenceStrategy -> String
showsPrec :: Int -> PersistenceStrategy -> ShowS
$cshowsPrec :: Int -> PersistenceStrategy -> ShowS
Show, ReadPrec [PersistenceStrategy]
ReadPrec PersistenceStrategy
Int -> ReadS PersistenceStrategy
ReadS [PersistenceStrategy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PersistenceStrategy]
$creadListPrec :: ReadPrec [PersistenceStrategy]
readPrec :: ReadPrec PersistenceStrategy
$creadPrec :: ReadPrec PersistenceStrategy
readList :: ReadS [PersistenceStrategy]
$creadList :: ReadS [PersistenceStrategy]
readsPrec :: Int -> ReadS PersistenceStrategy
$creadsPrec :: Int -> ReadS PersistenceStrategy
Read)
persistenceDirectory :: PersistenceStrategy -> Maybe FilePath
persistenceDirectory :: PersistenceStrategy -> Maybe String
persistenceDirectory PersistenceStrategy
NoPersistence = forall a. Maybe a
Nothing
persistenceDirectory (MinimalPersistence String
f) = forall a. a -> Maybe a
Just String
f
persistenceDirectory (CrashSafePersistence String
f) = forall a. a -> Maybe a
Just String
f
type AttributeExpr = AttributeExprBase ()
type GraphRefAttributeExpr = AttributeExprBase GraphRefTransactionMarker
data AttributeExprBase a = AttributeAndTypeNameExpr AttributeName TypeConstructor a |
NakedAttributeExpr Attribute
deriving (AttributeExprBase a -> AttributeExprBase a -> Bool
forall a.
Eq a =>
AttributeExprBase a -> AttributeExprBase a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AttributeExprBase a -> AttributeExprBase a -> Bool
$c/= :: forall a.
Eq a =>
AttributeExprBase a -> AttributeExprBase a -> Bool
== :: AttributeExprBase a -> AttributeExprBase a -> Bool
$c== :: forall a.
Eq a =>
AttributeExprBase a -> AttributeExprBase a -> Bool
Eq, Int -> AttributeExprBase a -> ShowS
forall a. Show a => Int -> AttributeExprBase a -> ShowS
forall a. Show a => [AttributeExprBase a] -> ShowS
forall a. Show a => AttributeExprBase a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AttributeExprBase a] -> ShowS
$cshowList :: forall a. Show a => [AttributeExprBase a] -> ShowS
show :: AttributeExprBase a -> String
$cshow :: forall a. Show a => AttributeExprBase a -> String
showsPrec :: Int -> AttributeExprBase a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> AttributeExprBase a -> ShowS
Show, ReadPrec [AttributeExprBase a]
ReadPrec (AttributeExprBase a)
ReadS [AttributeExprBase a]
forall a. Read a => ReadPrec [AttributeExprBase a]
forall a. Read a => ReadPrec (AttributeExprBase a)
forall a. Read a => Int -> ReadS (AttributeExprBase a)
forall a. Read a => ReadS [AttributeExprBase a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AttributeExprBase a]
$creadListPrec :: forall a. Read a => ReadPrec [AttributeExprBase a]
readPrec :: ReadPrec (AttributeExprBase a)
$creadPrec :: forall a. Read a => ReadPrec (AttributeExprBase a)
readList :: ReadS [AttributeExprBase a]
$creadList :: forall a. Read a => ReadS [AttributeExprBase a]
readsPrec :: Int -> ReadS (AttributeExprBase a)
$creadsPrec :: forall a. Read a => Int -> ReadS (AttributeExprBase a)
Read, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (AttributeExprBase a) x -> AttributeExprBase a
forall a x. AttributeExprBase a -> Rep (AttributeExprBase a) x
$cto :: forall a x. Rep (AttributeExprBase a) x -> AttributeExprBase a
$cfrom :: forall a x. AttributeExprBase a -> Rep (AttributeExprBase a) x
Generic, forall a. NFData a => AttributeExprBase a -> ()
forall a. (a -> ()) -> NFData a
rnf :: AttributeExprBase a -> ()
$crnf :: forall a. NFData a => AttributeExprBase a -> ()
NFData, forall a. Eq a => a -> AttributeExprBase a -> Bool
forall a. Num a => AttributeExprBase a -> a
forall a. Ord a => AttributeExprBase a -> a
forall m. Monoid m => AttributeExprBase m -> m
forall a. AttributeExprBase a -> Bool
forall a. AttributeExprBase a -> Int
forall a. AttributeExprBase a -> [a]
forall a. (a -> a -> a) -> AttributeExprBase a -> a
forall m a. Monoid m => (a -> m) -> AttributeExprBase a -> m
forall b a. (b -> a -> b) -> b -> AttributeExprBase a -> b
forall a b. (a -> b -> b) -> b -> AttributeExprBase a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: forall a. Num a => AttributeExprBase a -> a
$cproduct :: forall a. Num a => AttributeExprBase a -> a
sum :: forall a. Num a => AttributeExprBase a -> a
$csum :: forall a. Num a => AttributeExprBase a -> a
minimum :: forall a. Ord a => AttributeExprBase a -> a
$cminimum :: forall a. Ord a => AttributeExprBase a -> a
maximum :: forall a. Ord a => AttributeExprBase a -> a
$cmaximum :: forall a. Ord a => AttributeExprBase a -> a
elem :: forall a. Eq a => a -> AttributeExprBase a -> Bool
$celem :: forall a. Eq a => a -> AttributeExprBase a -> Bool
length :: forall a. AttributeExprBase a -> Int
$clength :: forall a. AttributeExprBase a -> Int
null :: forall a. AttributeExprBase a -> Bool
$cnull :: forall a. AttributeExprBase a -> Bool
toList :: forall a. AttributeExprBase a -> [a]
$ctoList :: forall a. AttributeExprBase a -> [a]
foldl1 :: forall a. (a -> a -> a) -> AttributeExprBase a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> AttributeExprBase a -> a
foldr1 :: forall a. (a -> a -> a) -> AttributeExprBase a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> AttributeExprBase a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> AttributeExprBase a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> AttributeExprBase a -> b
foldl :: forall b a. (b -> a -> b) -> b -> AttributeExprBase a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> AttributeExprBase a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> AttributeExprBase a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> AttributeExprBase a -> b
foldr :: forall a b. (a -> b -> b) -> b -> AttributeExprBase a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> AttributeExprBase a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> AttributeExprBase a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> AttributeExprBase a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> AttributeExprBase a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> AttributeExprBase a -> m
fold :: forall m. Monoid m => AttributeExprBase m -> m
$cfold :: forall m. Monoid m => AttributeExprBase m -> m
Foldable, forall a b. a -> AttributeExprBase b -> AttributeExprBase a
forall a b. (a -> b) -> AttributeExprBase a -> AttributeExprBase b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> AttributeExprBase b -> AttributeExprBase a
$c<$ :: forall a b. a -> AttributeExprBase b -> AttributeExprBase a
fmap :: forall a b. (a -> b) -> AttributeExprBase a -> AttributeExprBase b
$cfmap :: forall a b. (a -> b) -> AttributeExprBase a -> AttributeExprBase b
Functor, Functor AttributeExprBase
Foldable AttributeExprBase
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
AttributeExprBase (m a) -> m (AttributeExprBase a)
forall (f :: * -> *) a.
Applicative f =>
AttributeExprBase (f a) -> f (AttributeExprBase a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> AttributeExprBase a -> m (AttributeExprBase b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> AttributeExprBase a -> f (AttributeExprBase b)
sequence :: forall (m :: * -> *) a.
Monad m =>
AttributeExprBase (m a) -> m (AttributeExprBase a)
$csequence :: forall (m :: * -> *) a.
Monad m =>
AttributeExprBase (m a) -> m (AttributeExprBase a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> AttributeExprBase a -> m (AttributeExprBase b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> AttributeExprBase a -> m (AttributeExprBase b)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
AttributeExprBase (f a) -> f (AttributeExprBase a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
AttributeExprBase (f a) -> f (AttributeExprBase a)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> AttributeExprBase a -> f (AttributeExprBase b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> AttributeExprBase a -> f (AttributeExprBase b)
Traversable, forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
forall {a}. Hashable a => Eq (AttributeExprBase a)
forall a. Hashable a => Int -> AttributeExprBase a -> Int
forall a. Hashable a => AttributeExprBase a -> Int
hash :: AttributeExprBase a -> Int
$chash :: forall a. Hashable a => AttributeExprBase a -> Int
hashWithSalt :: Int -> AttributeExprBase a -> Int
$chashWithSalt :: forall a. Hashable a => Int -> AttributeExprBase a -> Int
Hashable)
newtype TupleExprBase a = TupleExpr (M.Map AttributeName (AtomExprBase a))
deriving (TupleExprBase a -> TupleExprBase a -> Bool
forall a. Eq a => TupleExprBase a -> TupleExprBase a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TupleExprBase a -> TupleExprBase a -> Bool
$c/= :: forall a. Eq a => TupleExprBase a -> TupleExprBase a -> Bool
== :: TupleExprBase a -> TupleExprBase a -> Bool
$c== :: forall a. Eq a => TupleExprBase a -> TupleExprBase a -> Bool
Eq, Int -> TupleExprBase a -> ShowS
forall a. Show a => Int -> TupleExprBase a -> ShowS
forall a. Show a => [TupleExprBase a] -> ShowS
forall a. Show a => TupleExprBase a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TupleExprBase a] -> ShowS
$cshowList :: forall a. Show a => [TupleExprBase a] -> ShowS
show :: TupleExprBase a -> String
$cshow :: forall a. Show a => TupleExprBase a -> String
showsPrec :: Int -> TupleExprBase a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> TupleExprBase a -> ShowS
Show, ReadPrec [TupleExprBase a]
ReadPrec (TupleExprBase a)
ReadS [TupleExprBase a]
forall a. Read a => ReadPrec [TupleExprBase a]
forall a. Read a => ReadPrec (TupleExprBase a)
forall a. Read a => Int -> ReadS (TupleExprBase a)
forall a. Read a => ReadS [TupleExprBase a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TupleExprBase a]
$creadListPrec :: forall a. Read a => ReadPrec [TupleExprBase a]
readPrec :: ReadPrec (TupleExprBase a)
$creadPrec :: forall a. Read a => ReadPrec (TupleExprBase a)
readList :: ReadS [TupleExprBase a]
$creadList :: forall a. Read a => ReadS [TupleExprBase a]
readsPrec :: Int -> ReadS (TupleExprBase a)
$creadsPrec :: forall a. Read a => Int -> ReadS (TupleExprBase a)
Read, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (TupleExprBase a) x -> TupleExprBase a
forall a x. TupleExprBase a -> Rep (TupleExprBase a) x
$cto :: forall a x. Rep (TupleExprBase a) x -> TupleExprBase a
$cfrom :: forall a x. TupleExprBase a -> Rep (TupleExprBase a) x
Generic, forall a. NFData a => TupleExprBase a -> ()
forall a. (a -> ()) -> NFData a
rnf :: TupleExprBase a -> ()
$crnf :: forall a. NFData a => TupleExprBase a -> ()
NFData, forall a. Eq a => a -> TupleExprBase a -> Bool
forall a. Num a => TupleExprBase a -> a
forall a. Ord a => TupleExprBase a -> a
forall m. Monoid m => TupleExprBase m -> m
forall a. TupleExprBase a -> Bool
forall a. TupleExprBase a -> Int
forall a. TupleExprBase a -> [a]
forall a. (a -> a -> a) -> TupleExprBase a -> a
forall m a. Monoid m => (a -> m) -> TupleExprBase a -> m
forall b a. (b -> a -> b) -> b -> TupleExprBase a -> b
forall a b. (a -> b -> b) -> b -> TupleExprBase a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: forall a. Num a => TupleExprBase a -> a
$cproduct :: forall a. Num a => TupleExprBase a -> a
sum :: forall a. Num a => TupleExprBase a -> a
$csum :: forall a. Num a => TupleExprBase a -> a
minimum :: forall a. Ord a => TupleExprBase a -> a
$cminimum :: forall a. Ord a => TupleExprBase a -> a
maximum :: forall a. Ord a => TupleExprBase a -> a
$cmaximum :: forall a. Ord a => TupleExprBase a -> a
elem :: forall a. Eq a => a -> TupleExprBase a -> Bool
$celem :: forall a. Eq a => a -> TupleExprBase a -> Bool
length :: forall a. TupleExprBase a -> Int
$clength :: forall a. TupleExprBase a -> Int
null :: forall a. TupleExprBase a -> Bool
$cnull :: forall a. TupleExprBase a -> Bool
toList :: forall a. TupleExprBase a -> [a]
$ctoList :: forall a. TupleExprBase a -> [a]
foldl1 :: forall a. (a -> a -> a) -> TupleExprBase a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> TupleExprBase a -> a
foldr1 :: forall a. (a -> a -> a) -> TupleExprBase a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> TupleExprBase a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> TupleExprBase a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> TupleExprBase a -> b
foldl :: forall b a. (b -> a -> b) -> b -> TupleExprBase a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> TupleExprBase a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> TupleExprBase a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> TupleExprBase a -> b
foldr :: forall a b. (a -> b -> b) -> b -> TupleExprBase a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> TupleExprBase a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> TupleExprBase a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> TupleExprBase a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> TupleExprBase a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> TupleExprBase a -> m
fold :: forall m. Monoid m => TupleExprBase m -> m
$cfold :: forall m. Monoid m => TupleExprBase m -> m
Foldable, forall a b. a -> TupleExprBase b -> TupleExprBase a
forall a b. (a -> b) -> TupleExprBase a -> TupleExprBase b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> TupleExprBase b -> TupleExprBase a
$c<$ :: forall a b. a -> TupleExprBase b -> TupleExprBase a
fmap :: forall a b. (a -> b) -> TupleExprBase a -> TupleExprBase b
$cfmap :: forall a b. (a -> b) -> TupleExprBase a -> TupleExprBase b
Functor, Functor TupleExprBase
Foldable TupleExprBase
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
TupleExprBase (m a) -> m (TupleExprBase a)
forall (f :: * -> *) a.
Applicative f =>
TupleExprBase (f a) -> f (TupleExprBase a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> TupleExprBase a -> m (TupleExprBase b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> TupleExprBase a -> f (TupleExprBase b)
sequence :: forall (m :: * -> *) a.
Monad m =>
TupleExprBase (m a) -> m (TupleExprBase a)
$csequence :: forall (m :: * -> *) a.
Monad m =>
TupleExprBase (m a) -> m (TupleExprBase a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> TupleExprBase a -> m (TupleExprBase b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> TupleExprBase a -> m (TupleExprBase b)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
TupleExprBase (f a) -> f (TupleExprBase a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
TupleExprBase (f a) -> f (TupleExprBase a)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> TupleExprBase a -> f (TupleExprBase b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> TupleExprBase a -> f (TupleExprBase b)
Traversable)
instance Hashable TupleExpr
type TupleExpr = TupleExprBase ()
type GraphRefTupleExpr = TupleExprBase GraphRefTransactionMarker
data TupleExprsBase a = TupleExprs a [TupleExprBase a]
deriving (TupleExprsBase a -> TupleExprsBase a -> Bool
forall a. Eq a => TupleExprsBase a -> TupleExprsBase a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TupleExprsBase a -> TupleExprsBase a -> Bool
$c/= :: forall a. Eq a => TupleExprsBase a -> TupleExprsBase a -> Bool
== :: TupleExprsBase a -> TupleExprsBase a -> Bool
$c== :: forall a. Eq a => TupleExprsBase a -> TupleExprsBase a -> Bool
Eq, Int -> TupleExprsBase a -> ShowS
forall a. Show a => Int -> TupleExprsBase a -> ShowS
forall a. Show a => [TupleExprsBase a] -> ShowS
forall a. Show a => TupleExprsBase a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TupleExprsBase a] -> ShowS
$cshowList :: forall a. Show a => [TupleExprsBase a] -> ShowS
show :: TupleExprsBase a -> String
$cshow :: forall a. Show a => TupleExprsBase a -> String
showsPrec :: Int -> TupleExprsBase a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> TupleExprsBase a -> ShowS
Show, ReadPrec [TupleExprsBase a]
ReadPrec (TupleExprsBase a)
ReadS [TupleExprsBase a]
forall a. Read a => ReadPrec [TupleExprsBase a]
forall a. Read a => ReadPrec (TupleExprsBase a)
forall a. Read a => Int -> ReadS (TupleExprsBase a)
forall a. Read a => ReadS [TupleExprsBase a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TupleExprsBase a]
$creadListPrec :: forall a. Read a => ReadPrec [TupleExprsBase a]
readPrec :: ReadPrec (TupleExprsBase a)
$creadPrec :: forall a. Read a => ReadPrec (TupleExprsBase a)
readList :: ReadS [TupleExprsBase a]
$creadList :: forall a. Read a => ReadS [TupleExprsBase a]
readsPrec :: Int -> ReadS (TupleExprsBase a)
$creadsPrec :: forall a. Read a => Int -> ReadS (TupleExprsBase a)
Read, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (TupleExprsBase a) x -> TupleExprsBase a
forall a x. TupleExprsBase a -> Rep (TupleExprsBase a) x
$cto :: forall a x. Rep (TupleExprsBase a) x -> TupleExprsBase a
$cfrom :: forall a x. TupleExprsBase a -> Rep (TupleExprsBase a) x
Generic, forall a. NFData a => TupleExprsBase a -> ()
forall a. (a -> ()) -> NFData a
rnf :: TupleExprsBase a -> ()
$crnf :: forall a. NFData a => TupleExprsBase a -> ()
NFData, forall a. Eq a => a -> TupleExprsBase a -> Bool
forall a. Num a => TupleExprsBase a -> a
forall a. Ord a => TupleExprsBase a -> a
forall m. Monoid m => TupleExprsBase m -> m
forall a. TupleExprsBase a -> Bool
forall a. TupleExprsBase a -> Int
forall a. TupleExprsBase a -> [a]
forall a. (a -> a -> a) -> TupleExprsBase a -> a
forall m a. Monoid m => (a -> m) -> TupleExprsBase a -> m
forall b a. (b -> a -> b) -> b -> TupleExprsBase a -> b
forall a b. (a -> b -> b) -> b -> TupleExprsBase a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: forall a. Num a => TupleExprsBase a -> a
$cproduct :: forall a. Num a => TupleExprsBase a -> a
sum :: forall a. Num a => TupleExprsBase a -> a
$csum :: forall a. Num a => TupleExprsBase a -> a
minimum :: forall a. Ord a => TupleExprsBase a -> a
$cminimum :: forall a. Ord a => TupleExprsBase a -> a
maximum :: forall a. Ord a => TupleExprsBase a -> a
$cmaximum :: forall a. Ord a => TupleExprsBase a -> a
elem :: forall a. Eq a => a -> TupleExprsBase a -> Bool
$celem :: forall a. Eq a => a -> TupleExprsBase a -> Bool
length :: forall a. TupleExprsBase a -> Int
$clength :: forall a. TupleExprsBase a -> Int
null :: forall a. TupleExprsBase a -> Bool
$cnull :: forall a. TupleExprsBase a -> Bool
toList :: forall a. TupleExprsBase a -> [a]
$ctoList :: forall a. TupleExprsBase a -> [a]
foldl1 :: forall a. (a -> a -> a) -> TupleExprsBase a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> TupleExprsBase a -> a
foldr1 :: forall a. (a -> a -> a) -> TupleExprsBase a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> TupleExprsBase a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> TupleExprsBase a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> TupleExprsBase a -> b
foldl :: forall b a. (b -> a -> b) -> b -> TupleExprsBase a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> TupleExprsBase a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> TupleExprsBase a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> TupleExprsBase a -> b
foldr :: forall a b. (a -> b -> b) -> b -> TupleExprsBase a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> TupleExprsBase a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> TupleExprsBase a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> TupleExprsBase a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> TupleExprsBase a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> TupleExprsBase a -> m
fold :: forall m. Monoid m => TupleExprsBase m -> m
$cfold :: forall m. Monoid m => TupleExprsBase m -> m
Foldable, forall a b. a -> TupleExprsBase b -> TupleExprsBase a
forall a b. (a -> b) -> TupleExprsBase a -> TupleExprsBase b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> TupleExprsBase b -> TupleExprsBase a
$c<$ :: forall a b. a -> TupleExprsBase b -> TupleExprsBase a
fmap :: forall a b. (a -> b) -> TupleExprsBase a -> TupleExprsBase b
$cfmap :: forall a b. (a -> b) -> TupleExprsBase a -> TupleExprsBase b
Functor, Functor TupleExprsBase
Foldable TupleExprsBase
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
TupleExprsBase (m a) -> m (TupleExprsBase a)
forall (f :: * -> *) a.
Applicative f =>
TupleExprsBase (f a) -> f (TupleExprsBase a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> TupleExprsBase a -> m (TupleExprsBase b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> TupleExprsBase a -> f (TupleExprsBase b)
sequence :: forall (m :: * -> *) a.
Monad m =>
TupleExprsBase (m a) -> m (TupleExprsBase a)
$csequence :: forall (m :: * -> *) a.
Monad m =>
TupleExprsBase (m a) -> m (TupleExprsBase a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> TupleExprsBase a -> m (TupleExprsBase b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> TupleExprsBase a -> m (TupleExprsBase b)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
TupleExprsBase (f a) -> f (TupleExprsBase a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
TupleExprsBase (f a) -> f (TupleExprsBase a)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> TupleExprsBase a -> f (TupleExprsBase b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> TupleExprsBase a -> f (TupleExprsBase b)
Traversable)
instance Hashable TupleExprs
type GraphRefTupleExprs = TupleExprsBase GraphRefTransactionMarker
type TupleExprs = TupleExprsBase ()
data MergeStrategy =
UnionMergeStrategy |
UnionPreferMergeStrategy HeadName |
SelectedBranchMergeStrategy HeadName
deriving (MergeStrategy -> MergeStrategy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MergeStrategy -> MergeStrategy -> Bool
$c/= :: MergeStrategy -> MergeStrategy -> Bool
== :: MergeStrategy -> MergeStrategy -> Bool
$c== :: MergeStrategy -> MergeStrategy -> Bool
Eq, Int -> MergeStrategy -> ShowS
[MergeStrategy] -> ShowS
MergeStrategy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MergeStrategy] -> ShowS
$cshowList :: [MergeStrategy] -> ShowS
show :: MergeStrategy -> String
$cshow :: MergeStrategy -> String
showsPrec :: Int -> MergeStrategy -> ShowS
$cshowsPrec :: Int -> MergeStrategy -> ShowS
Show, forall x. Rep MergeStrategy x -> MergeStrategy
forall x. MergeStrategy -> Rep MergeStrategy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MergeStrategy x -> MergeStrategy
$cfrom :: forall x. MergeStrategy -> Rep MergeStrategy x
Generic, MergeStrategy -> ()
forall a. (a -> ()) -> NFData a
rnf :: MergeStrategy -> ()
$crnf :: MergeStrategy -> ()
NFData)
type DatabaseContextFunctionBodyType = [Atom] -> DatabaseContext -> Either DatabaseContextFunctionError DatabaseContext
type DatabaseContextFunctions = HS.HashSet DatabaseContextFunction
type FunctionName = StringType
type FunctionBodyScript = StringType
data Function a = Function {
forall a. Function a -> Text
funcName :: FunctionName,
forall a. Function a -> [AtomType]
funcType :: [AtomType],
forall a. Function a -> FunctionBody a
funcBody :: FunctionBody a
}
deriving (forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (Function a) x -> Function a
forall a x. Function a -> Rep (Function a) x
$cto :: forall a x. Rep (Function a) x -> Function a
$cfrom :: forall a x. Function a -> Rep (Function a) x
Generic, forall a. NFData a => Function a -> ()
forall a. (a -> ()) -> NFData a
rnf :: Function a -> ()
$crnf :: forall a. NFData a => Function a -> ()
NFData)
instance Eq (Function a) where
Function a
f1 == :: Function a -> Function a -> Bool
== Function a
f2 = forall a. Function a -> Text
funcName Function a
f1 forall a. Eq a => a -> a -> Bool
== forall a. Function a -> Text
funcName Function a
f2
instance Hashable (Function a) where
hashWithSalt :: Int -> Function a -> Int
hashWithSalt Int
salt Function a
func = Int
salt forall a. Hashable a => Int -> a -> Int
`hashWithSalt` forall a. Function a -> Text
funcName Function a
func forall a. Hashable a => Int -> a -> Int
`hashWithSalt` forall a. Function a -> [AtomType]
funcType Function a
func forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Int
hashfuncbody
where
hashfuncbody :: Int
hashfuncbody =
case forall a. Function a -> FunctionBody a
funcBody Function a
func of
(FunctionScriptBody Text
script a
_) -> Int
salt forall a. Hashable a => Int -> a -> Int
`hashWithSalt` Text
script
(FunctionBuiltInBody a
_) -> Int
salt
(FunctionObjectLoadedBody String
fp String
modName String
entryFunc a
_) -> Int
salt forall a. Hashable a => Int -> a -> Int
`hashWithSalt` (String
fp, String
modName, String
entryFunc)
data FunctionBody a =
FunctionScriptBody FunctionBodyScript a |
FunctionBuiltInBody a |
FunctionObjectLoadedBody FilePath ObjectModuleName ObjectFileEntryFunctionName a
deriving forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (FunctionBody a) x -> FunctionBody a
forall a x. FunctionBody a -> Rep (FunctionBody a) x
$cto :: forall a x. Rep (FunctionBody a) x -> FunctionBody a
$cfrom :: forall a x. FunctionBody a -> Rep (FunctionBody a) x
Generic
instance NFData a => NFData (FunctionBody a) where
rnf :: FunctionBody a -> ()
rnf (FunctionScriptBody Text
script a
_) = forall a. NFData a => a -> ()
rnf Text
script
rnf (FunctionBuiltInBody a
_) = forall a. NFData a => a -> ()
rnf ()
rnf (FunctionObjectLoadedBody String
fp String
mod' String
entryf a
_) = forall a. NFData a => a -> ()
rnf (String
fp, String
mod', String
entryf)
type AtomFunction = Function AtomFunctionBodyType
type AtomFunctionBody = FunctionBody AtomFunctionBodyType
type DatabaseContextFunction = Function DatabaseContextFunctionBodyType
type DatabaseContextFunctionBody = FunctionBody DatabaseContextFunctionBodyType
attrTypeVars :: Attribute -> S.Set TypeVarName
attrTypeVars :: Attribute -> Set Text
attrTypeVars (Attribute Text
_ AtomType
aType) = case AtomType
aType of
AtomType
IntAtomType -> forall a. Set a
S.empty
AtomType
IntegerAtomType -> forall a. Set a
S.empty
AtomType
ScientificAtomType -> forall a. Set a
S.empty
AtomType
DoubleAtomType -> forall a. Set a
S.empty
AtomType
TextAtomType -> forall a. Set a
S.empty
AtomType
DayAtomType -> forall a. Set a
S.empty
AtomType
DateTimeAtomType -> forall a. Set a
S.empty
AtomType
ByteStringAtomType -> forall a. Set a
S.empty
AtomType
BoolAtomType -> forall a. Set a
S.empty
AtomType
UUIDAtomType -> forall a. Set a
S.empty
AtomType
RelationalExprAtomType -> forall a. Set a
S.empty
SubrelationFoldAtomType{} -> forall a. Set a
S.empty
(RelationAtomType Attributes
attrs) -> forall (f :: * -> *) a. (Foldable f, Ord a) => f (Set a) -> Set a
S.unions (forall a b. (a -> b) -> [a] -> [b]
map Attribute -> Set Text
attrTypeVars (forall a. Vector a -> [a]
V.toList (Attributes -> Vector Attribute
attributesVec Attributes
attrs)))
(ConstructedAtomType Text
_ TypeVarMap
tvMap) -> forall k a. Map k a -> Set k
M.keysSet TypeVarMap
tvMap
(TypeVariableType Text
nam) -> forall a. a -> Set a
S.singleton Text
nam
typeVars :: TypeConstructor -> S.Set TypeVarName
typeVars :: TypeConstructor -> Set Text
typeVars (PrimitiveTypeConstructor Text
_ AtomType
_) = forall a. Set a
S.empty
typeVars (ADTypeConstructor Text
_ [TypeConstructor]
args) = forall (f :: * -> *) a. (Foldable f, Ord a) => f (Set a) -> Set a
S.unions (forall a b. (a -> b) -> [a] -> [b]
map TypeConstructor -> Set Text
typeVars [TypeConstructor]
args)
typeVars (TypeVariable Text
v) = forall a. a -> Set a
S.singleton Text
v
typeVars (RelationAtomTypeConstructor [AttributeExprBase ()]
attrExprs) = forall (f :: * -> *) a. (Foldable f, Ord a) => f (Set a) -> Set a
S.unions (forall a b. (a -> b) -> [a] -> [b]
map forall a. AttributeExprBase a -> Set Text
attrExprTypeVars [AttributeExprBase ()]
attrExprs)
attrExprTypeVars :: AttributeExprBase a -> S.Set TypeVarName
attrExprTypeVars :: forall a. AttributeExprBase a -> Set Text
attrExprTypeVars (AttributeAndTypeNameExpr Text
_ TypeConstructor
tCons a
_) = TypeConstructor -> Set Text
typeVars TypeConstructor
tCons
attrExprTypeVars (NakedAttributeExpr Attribute
attr) = Attribute -> Set Text
attrTypeVars Attribute
attr
atomTypeVars :: AtomType -> S.Set TypeVarName
atomTypeVars :: AtomType -> Set Text
atomTypeVars AtomType
IntAtomType = forall a. Set a
S.empty
atomTypeVars AtomType
IntegerAtomType = forall a. Set a
S.empty
atomTypeVars AtomType
ScientificAtomType = forall a. Set a
S.empty
atomTypeVars AtomType
DoubleAtomType = forall a. Set a
S.empty
atomTypeVars AtomType
TextAtomType = forall a. Set a
S.empty
atomTypeVars AtomType
DayAtomType = forall a. Set a
S.empty
atomTypeVars AtomType
DateTimeAtomType = forall a. Set a
S.empty
atomTypeVars AtomType
ByteStringAtomType = forall a. Set a
S.empty
atomTypeVars AtomType
BoolAtomType = forall a. Set a
S.empty
atomTypeVars AtomType
UUIDAtomType = forall a. Set a
S.empty
atomTypeVars AtomType
RelationalExprAtomType = forall a. Set a
S.empty
atomTypeVars SubrelationFoldAtomType{} = forall a. Set a
S.empty
atomTypeVars (RelationAtomType Attributes
attrs) = forall (f :: * -> *) a. (Foldable f, Ord a) => f (Set a) -> Set a
S.unions (forall a b. (a -> b) -> [a] -> [b]
map Attribute -> Set Text
attrTypeVars (forall a. Vector a -> [a]
V.toList (Attributes -> Vector Attribute
attributesVec Attributes
attrs)))
atomTypeVars (ConstructedAtomType Text
_ TypeVarMap
tvMap) = forall k a. Map k a -> Set k
M.keysSet TypeVarMap
tvMap
atomTypeVars (TypeVariableType Text
nam) = forall a. a -> Set a
S.singleton Text
nam
unimplemented :: HasCallStack => a
unimplemented :: forall a. HasCallStack => a
unimplemented = forall a. HasCallStack => String -> a
error String
"unimplemented"
makeBaseFunctor ''RelationalExprBase