{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# OPTIONS_GHC -fno-warn-unused-top-binds #-}
module Gram.CST
( Gram(..)
, AnnotatedPattern(..)
, PatternElement(..)
, Path(..)
, PathSegment(..)
, Node(..)
, Relationship(..)
, SubjectPattern(..)
, SubjectData(..)
, Annotation(..)
, Identifier(..)
, Symbol(..)
, Value
, RangeValue
) where
import GHC.Generics (Generic)
import Data.Map (Map)
import Data.Set (Set)
import qualified Subject.Value as CoreVal
data Gram = Gram
{ Gram -> Maybe (Map String Value)
gramRecord :: Maybe (Map String Value)
, Gram -> [AnnotatedPattern]
gramPatterns :: [AnnotatedPattern]
} deriving (Int -> Gram -> ShowS
[Gram] -> ShowS
Gram -> String
(Int -> Gram -> ShowS)
-> (Gram -> String) -> ([Gram] -> ShowS) -> Show Gram
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Gram -> ShowS
showsPrec :: Int -> Gram -> ShowS
$cshow :: Gram -> String
show :: Gram -> String
$cshowList :: [Gram] -> ShowS
showList :: [Gram] -> ShowS
Show, Gram -> Gram -> Bool
(Gram -> Gram -> Bool) -> (Gram -> Gram -> Bool) -> Eq Gram
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Gram -> Gram -> Bool
== :: Gram -> Gram -> Bool
$c/= :: Gram -> Gram -> Bool
/= :: Gram -> Gram -> Bool
Eq, (forall x. Gram -> Rep Gram x)
-> (forall x. Rep Gram x -> Gram) -> Generic Gram
forall x. Rep Gram x -> Gram
forall x. Gram -> Rep Gram x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Gram -> Rep Gram x
from :: forall x. Gram -> Rep Gram x
$cto :: forall x. Rep Gram x -> Gram
to :: forall x. Rep Gram x -> Gram
Generic)
data AnnotatedPattern = AnnotatedPattern
{ AnnotatedPattern -> [Annotation]
apAnnotations :: [Annotation]
, AnnotatedPattern -> [PatternElement]
apElements :: [PatternElement]
} deriving (Int -> AnnotatedPattern -> ShowS
[AnnotatedPattern] -> ShowS
AnnotatedPattern -> String
(Int -> AnnotatedPattern -> ShowS)
-> (AnnotatedPattern -> String)
-> ([AnnotatedPattern] -> ShowS)
-> Show AnnotatedPattern
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AnnotatedPattern -> ShowS
showsPrec :: Int -> AnnotatedPattern -> ShowS
$cshow :: AnnotatedPattern -> String
show :: AnnotatedPattern -> String
$cshowList :: [AnnotatedPattern] -> ShowS
showList :: [AnnotatedPattern] -> ShowS
Show, AnnotatedPattern -> AnnotatedPattern -> Bool
(AnnotatedPattern -> AnnotatedPattern -> Bool)
-> (AnnotatedPattern -> AnnotatedPattern -> Bool)
-> Eq AnnotatedPattern
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AnnotatedPattern -> AnnotatedPattern -> Bool
== :: AnnotatedPattern -> AnnotatedPattern -> Bool
$c/= :: AnnotatedPattern -> AnnotatedPattern -> Bool
/= :: AnnotatedPattern -> AnnotatedPattern -> Bool
Eq, (forall x. AnnotatedPattern -> Rep AnnotatedPattern x)
-> (forall x. Rep AnnotatedPattern x -> AnnotatedPattern)
-> Generic AnnotatedPattern
forall x. Rep AnnotatedPattern x -> AnnotatedPattern
forall x. AnnotatedPattern -> Rep AnnotatedPattern x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. AnnotatedPattern -> Rep AnnotatedPattern x
from :: forall x. AnnotatedPattern -> Rep AnnotatedPattern x
$cto :: forall x. Rep AnnotatedPattern x -> AnnotatedPattern
to :: forall x. Rep AnnotatedPattern x -> AnnotatedPattern
Generic)
data PatternElement
= PEPath Path
| PESubjectPattern SubjectPattern
| PEReference Identifier
deriving (Int -> PatternElement -> ShowS
[PatternElement] -> ShowS
PatternElement -> String
(Int -> PatternElement -> ShowS)
-> (PatternElement -> String)
-> ([PatternElement] -> ShowS)
-> Show PatternElement
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PatternElement -> ShowS
showsPrec :: Int -> PatternElement -> ShowS
$cshow :: PatternElement -> String
show :: PatternElement -> String
$cshowList :: [PatternElement] -> ShowS
showList :: [PatternElement] -> ShowS
Show, PatternElement -> PatternElement -> Bool
(PatternElement -> PatternElement -> Bool)
-> (PatternElement -> PatternElement -> Bool) -> Eq PatternElement
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PatternElement -> PatternElement -> Bool
== :: PatternElement -> PatternElement -> Bool
$c/= :: PatternElement -> PatternElement -> Bool
/= :: PatternElement -> PatternElement -> Bool
Eq, (forall x. PatternElement -> Rep PatternElement x)
-> (forall x. Rep PatternElement x -> PatternElement)
-> Generic PatternElement
forall x. Rep PatternElement x -> PatternElement
forall x. PatternElement -> Rep PatternElement x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PatternElement -> Rep PatternElement x
from :: forall x. PatternElement -> Rep PatternElement x
$cto :: forall x. Rep PatternElement x -> PatternElement
to :: forall x. Rep PatternElement x -> PatternElement
Generic)
data Path = Path
{ Path -> Node
pathStart :: Node
, Path -> [PathSegment]
pathSegments :: [PathSegment]
} deriving (Int -> Path -> ShowS
[Path] -> ShowS
Path -> String
(Int -> Path -> ShowS)
-> (Path -> String) -> ([Path] -> ShowS) -> Show Path
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Path -> ShowS
showsPrec :: Int -> Path -> ShowS
$cshow :: Path -> String
show :: Path -> String
$cshowList :: [Path] -> ShowS
showList :: [Path] -> ShowS
Show, Path -> Path -> Bool
(Path -> Path -> Bool) -> (Path -> Path -> Bool) -> Eq Path
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Path -> Path -> Bool
== :: Path -> Path -> Bool
$c/= :: Path -> Path -> Bool
/= :: Path -> Path -> Bool
Eq, (forall x. Path -> Rep Path x)
-> (forall x. Rep Path x -> Path) -> Generic Path
forall x. Rep Path x -> Path
forall x. Path -> Rep Path x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Path -> Rep Path x
from :: forall x. Path -> Rep Path x
$cto :: forall x. Rep Path x -> Path
to :: forall x. Rep Path x -> Path
Generic)
data PathSegment = PathSegment
{ PathSegment -> Relationship
segmentRel :: Relationship
, PathSegment -> Node
segmentNode :: Node
} deriving (Int -> PathSegment -> ShowS
[PathSegment] -> ShowS
PathSegment -> String
(Int -> PathSegment -> ShowS)
-> (PathSegment -> String)
-> ([PathSegment] -> ShowS)
-> Show PathSegment
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PathSegment -> ShowS
showsPrec :: Int -> PathSegment -> ShowS
$cshow :: PathSegment -> String
show :: PathSegment -> String
$cshowList :: [PathSegment] -> ShowS
showList :: [PathSegment] -> ShowS
Show, PathSegment -> PathSegment -> Bool
(PathSegment -> PathSegment -> Bool)
-> (PathSegment -> PathSegment -> Bool) -> Eq PathSegment
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PathSegment -> PathSegment -> Bool
== :: PathSegment -> PathSegment -> Bool
$c/= :: PathSegment -> PathSegment -> Bool
/= :: PathSegment -> PathSegment -> Bool
Eq, (forall x. PathSegment -> Rep PathSegment x)
-> (forall x. Rep PathSegment x -> PathSegment)
-> Generic PathSegment
forall x. Rep PathSegment x -> PathSegment
forall x. PathSegment -> Rep PathSegment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PathSegment -> Rep PathSegment x
from :: forall x. PathSegment -> Rep PathSegment x
$cto :: forall x. Rep PathSegment x -> PathSegment
to :: forall x. Rep PathSegment x -> PathSegment
Generic)
data Node = Node
{ Node -> Maybe SubjectData
nodeSubject :: Maybe SubjectData
} deriving (Int -> Node -> ShowS
[Node] -> ShowS
Node -> String
(Int -> Node -> ShowS)
-> (Node -> String) -> ([Node] -> ShowS) -> Show Node
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Node -> ShowS
showsPrec :: Int -> Node -> ShowS
$cshow :: Node -> String
show :: Node -> String
$cshowList :: [Node] -> ShowS
showList :: [Node] -> ShowS
Show, Node -> Node -> Bool
(Node -> Node -> Bool) -> (Node -> Node -> Bool) -> Eq Node
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Node -> Node -> Bool
== :: Node -> Node -> Bool
$c/= :: Node -> Node -> Bool
/= :: Node -> Node -> Bool
Eq, (forall x. Node -> Rep Node x)
-> (forall x. Rep Node x -> Node) -> Generic Node
forall x. Rep Node x -> Node
forall x. Node -> Rep Node x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Node -> Rep Node x
from :: forall x. Node -> Rep Node x
$cto :: forall x. Rep Node x -> Node
to :: forall x. Rep Node x -> Node
Generic)
data Relationship = Relationship
{ Relationship -> String
relArrow :: String
, Relationship -> Maybe SubjectData
relSubject :: Maybe SubjectData
} deriving (Int -> Relationship -> ShowS
[Relationship] -> ShowS
Relationship -> String
(Int -> Relationship -> ShowS)
-> (Relationship -> String)
-> ([Relationship] -> ShowS)
-> Show Relationship
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Relationship -> ShowS
showsPrec :: Int -> Relationship -> ShowS
$cshow :: Relationship -> String
show :: Relationship -> String
$cshowList :: [Relationship] -> ShowS
showList :: [Relationship] -> ShowS
Show, Relationship -> Relationship -> Bool
(Relationship -> Relationship -> Bool)
-> (Relationship -> Relationship -> Bool) -> Eq Relationship
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Relationship -> Relationship -> Bool
== :: Relationship -> Relationship -> Bool
$c/= :: Relationship -> Relationship -> Bool
/= :: Relationship -> Relationship -> Bool
Eq, (forall x. Relationship -> Rep Relationship x)
-> (forall x. Rep Relationship x -> Relationship)
-> Generic Relationship
forall x. Rep Relationship x -> Relationship
forall x. Relationship -> Rep Relationship x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Relationship -> Rep Relationship x
from :: forall x. Relationship -> Rep Relationship x
$cto :: forall x. Rep Relationship x -> Relationship
to :: forall x. Rep Relationship x -> Relationship
Generic)
data SubjectPattern = SubjectPattern
{ SubjectPattern -> Maybe SubjectData
spSubject :: Maybe SubjectData
, SubjectPattern -> [PatternElement]
spElements :: [PatternElement]
} deriving (Int -> SubjectPattern -> ShowS
[SubjectPattern] -> ShowS
SubjectPattern -> String
(Int -> SubjectPattern -> ShowS)
-> (SubjectPattern -> String)
-> ([SubjectPattern] -> ShowS)
-> Show SubjectPattern
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SubjectPattern -> ShowS
showsPrec :: Int -> SubjectPattern -> ShowS
$cshow :: SubjectPattern -> String
show :: SubjectPattern -> String
$cshowList :: [SubjectPattern] -> ShowS
showList :: [SubjectPattern] -> ShowS
Show, SubjectPattern -> SubjectPattern -> Bool
(SubjectPattern -> SubjectPattern -> Bool)
-> (SubjectPattern -> SubjectPattern -> Bool) -> Eq SubjectPattern
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SubjectPattern -> SubjectPattern -> Bool
== :: SubjectPattern -> SubjectPattern -> Bool
$c/= :: SubjectPattern -> SubjectPattern -> Bool
/= :: SubjectPattern -> SubjectPattern -> Bool
Eq, (forall x. SubjectPattern -> Rep SubjectPattern x)
-> (forall x. Rep SubjectPattern x -> SubjectPattern)
-> Generic SubjectPattern
forall x. Rep SubjectPattern x -> SubjectPattern
forall x. SubjectPattern -> Rep SubjectPattern x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SubjectPattern -> Rep SubjectPattern x
from :: forall x. SubjectPattern -> Rep SubjectPattern x
$cto :: forall x. Rep SubjectPattern x -> SubjectPattern
to :: forall x. Rep SubjectPattern x -> SubjectPattern
Generic)
data SubjectData = SubjectData
{ SubjectData -> Maybe Identifier
dataIdentifier :: Maybe Identifier
, SubjectData -> Set String
dataLabels :: Set String
, SubjectData -> Map String Value
dataProperties :: Map String Value
} deriving (Int -> SubjectData -> ShowS
[SubjectData] -> ShowS
SubjectData -> String
(Int -> SubjectData -> ShowS)
-> (SubjectData -> String)
-> ([SubjectData] -> ShowS)
-> Show SubjectData
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SubjectData -> ShowS
showsPrec :: Int -> SubjectData -> ShowS
$cshow :: SubjectData -> String
show :: SubjectData -> String
$cshowList :: [SubjectData] -> ShowS
showList :: [SubjectData] -> ShowS
Show, SubjectData -> SubjectData -> Bool
(SubjectData -> SubjectData -> Bool)
-> (SubjectData -> SubjectData -> Bool) -> Eq SubjectData
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SubjectData -> SubjectData -> Bool
== :: SubjectData -> SubjectData -> Bool
$c/= :: SubjectData -> SubjectData -> Bool
/= :: SubjectData -> SubjectData -> Bool
Eq, (forall x. SubjectData -> Rep SubjectData x)
-> (forall x. Rep SubjectData x -> SubjectData)
-> Generic SubjectData
forall x. Rep SubjectData x -> SubjectData
forall x. SubjectData -> Rep SubjectData x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SubjectData -> Rep SubjectData x
from :: forall x. SubjectData -> Rep SubjectData x
$cto :: forall x. Rep SubjectData x -> SubjectData
to :: forall x. Rep SubjectData x -> SubjectData
Generic)
data Annotation = Annotation
{ Annotation -> Symbol
annKey :: Symbol
, Annotation -> Value
annValue :: Value
} deriving (Int -> Annotation -> ShowS
[Annotation] -> ShowS
Annotation -> String
(Int -> Annotation -> ShowS)
-> (Annotation -> String)
-> ([Annotation] -> ShowS)
-> Show Annotation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Annotation -> ShowS
showsPrec :: Int -> Annotation -> ShowS
$cshow :: Annotation -> String
show :: Annotation -> String
$cshowList :: [Annotation] -> ShowS
showList :: [Annotation] -> ShowS
Show, Annotation -> Annotation -> Bool
(Annotation -> Annotation -> Bool)
-> (Annotation -> Annotation -> Bool) -> Eq Annotation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Annotation -> Annotation -> Bool
== :: Annotation -> Annotation -> Bool
$c/= :: Annotation -> Annotation -> Bool
/= :: Annotation -> Annotation -> Bool
Eq, (forall x. Annotation -> Rep Annotation x)
-> (forall x. Rep Annotation x -> Annotation) -> Generic Annotation
forall x. Rep Annotation x -> Annotation
forall x. Annotation -> Rep Annotation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Annotation -> Rep Annotation x
from :: forall x. Annotation -> Rep Annotation x
$cto :: forall x. Rep Annotation x -> Annotation
to :: forall x. Rep Annotation x -> Annotation
Generic)
newtype Symbol = Symbol String
deriving (Int -> Symbol -> ShowS
[Symbol] -> ShowS
Symbol -> String
(Int -> Symbol -> ShowS)
-> (Symbol -> String) -> ([Symbol] -> ShowS) -> Show Symbol
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Symbol -> ShowS
showsPrec :: Int -> Symbol -> ShowS
$cshow :: Symbol -> String
show :: Symbol -> String
$cshowList :: [Symbol] -> ShowS
showList :: [Symbol] -> ShowS
Show, Symbol -> Symbol -> Bool
(Symbol -> Symbol -> Bool)
-> (Symbol -> Symbol -> Bool) -> Eq Symbol
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Symbol -> Symbol -> Bool
== :: Symbol -> Symbol -> Bool
$c/= :: Symbol -> Symbol -> Bool
/= :: Symbol -> Symbol -> Bool
Eq, Eq Symbol
Eq Symbol =>
(Symbol -> Symbol -> Ordering)
-> (Symbol -> Symbol -> Bool)
-> (Symbol -> Symbol -> Bool)
-> (Symbol -> Symbol -> Bool)
-> (Symbol -> Symbol -> Bool)
-> (Symbol -> Symbol -> Symbol)
-> (Symbol -> Symbol -> Symbol)
-> Ord Symbol
Symbol -> Symbol -> Bool
Symbol -> Symbol -> Ordering
Symbol -> Symbol -> Symbol
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
$ccompare :: Symbol -> Symbol -> Ordering
compare :: Symbol -> Symbol -> Ordering
$c< :: Symbol -> Symbol -> Bool
< :: Symbol -> Symbol -> Bool
$c<= :: Symbol -> Symbol -> Bool
<= :: Symbol -> Symbol -> Bool
$c> :: Symbol -> Symbol -> Bool
> :: Symbol -> Symbol -> Bool
$c>= :: Symbol -> Symbol -> Bool
>= :: Symbol -> Symbol -> Bool
$cmax :: Symbol -> Symbol -> Symbol
max :: Symbol -> Symbol -> Symbol
$cmin :: Symbol -> Symbol -> Symbol
min :: Symbol -> Symbol -> Symbol
Ord, (forall x. Symbol -> Rep Symbol x)
-> (forall x. Rep Symbol x -> Symbol) -> Generic Symbol
forall x. Rep Symbol x -> Symbol
forall x. Symbol -> Rep Symbol x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Symbol -> Rep Symbol x
from :: forall x. Symbol -> Rep Symbol x
$cto :: forall x. Rep Symbol x -> Symbol
to :: forall x. Rep Symbol x -> Symbol
Generic)
data Identifier
= IdentSymbol Symbol
| IdentString String
| IdentInteger Integer
deriving (Int -> Identifier -> ShowS
[Identifier] -> ShowS
Identifier -> String
(Int -> Identifier -> ShowS)
-> (Identifier -> String)
-> ([Identifier] -> ShowS)
-> Show Identifier
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Identifier -> ShowS
showsPrec :: Int -> Identifier -> ShowS
$cshow :: Identifier -> String
show :: Identifier -> String
$cshowList :: [Identifier] -> ShowS
showList :: [Identifier] -> ShowS
Show, Identifier -> Identifier -> Bool
(Identifier -> Identifier -> Bool)
-> (Identifier -> Identifier -> Bool) -> Eq Identifier
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Identifier -> Identifier -> Bool
== :: Identifier -> Identifier -> Bool
$c/= :: Identifier -> Identifier -> Bool
/= :: Identifier -> Identifier -> Bool
Eq, Eq Identifier
Eq Identifier =>
(Identifier -> Identifier -> Ordering)
-> (Identifier -> Identifier -> Bool)
-> (Identifier -> Identifier -> Bool)
-> (Identifier -> Identifier -> Bool)
-> (Identifier -> Identifier -> Bool)
-> (Identifier -> Identifier -> Identifier)
-> (Identifier -> Identifier -> Identifier)
-> Ord Identifier
Identifier -> Identifier -> Bool
Identifier -> Identifier -> Ordering
Identifier -> Identifier -> Identifier
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
$ccompare :: Identifier -> Identifier -> Ordering
compare :: Identifier -> Identifier -> Ordering
$c< :: Identifier -> Identifier -> Bool
< :: Identifier -> Identifier -> Bool
$c<= :: Identifier -> Identifier -> Bool
<= :: Identifier -> Identifier -> Bool
$c> :: Identifier -> Identifier -> Bool
> :: Identifier -> Identifier -> Bool
$c>= :: Identifier -> Identifier -> Bool
>= :: Identifier -> Identifier -> Bool
$cmax :: Identifier -> Identifier -> Identifier
max :: Identifier -> Identifier -> Identifier
$cmin :: Identifier -> Identifier -> Identifier
min :: Identifier -> Identifier -> Identifier
Ord, (forall x. Identifier -> Rep Identifier x)
-> (forall x. Rep Identifier x -> Identifier) -> Generic Identifier
forall x. Rep Identifier x -> Identifier
forall x. Identifier -> Rep Identifier x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Identifier -> Rep Identifier x
from :: forall x. Identifier -> Rep Identifier x
$cto :: forall x. Rep Identifier x -> Identifier
to :: forall x. Rep Identifier x -> Identifier
Generic)
{-# OPTIONS_GHC -fno-warn-unused-top-binds #-}
type Value = CoreVal.Value
type RangeValue = CoreVal.RangeValue