{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DerivingStrategies #-}
module Codec.CBOR.Cuddle.CDDL (
CDDL (..),
sortCDDL,
cddlTopLevel,
cddlRules,
fromRules,
fromRule,
TopLevel (..),
Name (..),
Rule (..),
TypeOrGroup (..),
Assign (..),
GenericArg (..),
GenericParam (..),
Type0 (..),
Type1 (..),
Type2 (..),
TyOp (..),
RangeBound (..),
OccurrenceIndicator (..),
Group (..),
GroupEntry (..),
GroupEntryVariant (..),
MemberKey (..),
Value (..),
value,
ValueVariant (..),
GrpChoice (..),
unwrap,
compareRuleName,
) where
import Codec.CBOR.Cuddle.CDDL.CtlOp (CtlOp)
import Codec.CBOR.Cuddle.Comments (CollectComments (..), Comment, HasComment (..))
import Data.ByteString qualified as B
import Data.Default.Class (Default (..))
import Data.Function (on, (&))
import Data.Hashable (Hashable)
import Data.List.NonEmpty (NonEmpty (..))
import Data.List.NonEmpty qualified as NE
import Data.String (IsString (..))
import Data.Text qualified as T
import Data.TreeDiff (ToExpr)
import Data.Word (Word64, Word8)
import GHC.Generics (Generic)
import Optics.Core ((%), (.~))
import Optics.Getter (view)
import Optics.Lens (lens)
data CDDL = CDDL [Comment] Rule [TopLevel]
deriving (CDDL -> CDDL -> Bool
(CDDL -> CDDL -> Bool) -> (CDDL -> CDDL -> Bool) -> Eq CDDL
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CDDL -> CDDL -> Bool
== :: CDDL -> CDDL -> Bool
$c/= :: CDDL -> CDDL -> Bool
/= :: CDDL -> CDDL -> Bool
Eq, (forall x. CDDL -> Rep CDDL x)
-> (forall x. Rep CDDL x -> CDDL) -> Generic CDDL
forall x. Rep CDDL x -> CDDL
forall x. CDDL -> Rep CDDL x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CDDL -> Rep CDDL x
from :: forall x. CDDL -> Rep CDDL x
$cto :: forall x. Rep CDDL x -> CDDL
to :: forall x. Rep CDDL x -> CDDL
Generic, Int -> CDDL -> ShowS
[CDDL] -> ShowS
CDDL -> String
(Int -> CDDL -> ShowS)
-> (CDDL -> String) -> ([CDDL] -> ShowS) -> Show CDDL
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CDDL -> ShowS
showsPrec :: Int -> CDDL -> ShowS
$cshow :: CDDL -> String
show :: CDDL -> String
$cshowList :: [CDDL] -> ShowS
showList :: [CDDL] -> ShowS
Show, [CDDL] -> Expr
CDDL -> Expr
(CDDL -> Expr) -> ([CDDL] -> Expr) -> ToExpr CDDL
forall a. (a -> Expr) -> ([a] -> Expr) -> ToExpr a
$ctoExpr :: CDDL -> Expr
toExpr :: CDDL -> Expr
$clistToExpr :: [CDDL] -> Expr
listToExpr :: [CDDL] -> Expr
ToExpr)
sortCDDL :: CDDL -> CDDL
sortCDDL :: CDDL -> CDDL
sortCDDL = NonEmpty Rule -> CDDL
fromRules (NonEmpty Rule -> CDDL) -> (CDDL -> NonEmpty Rule) -> CDDL -> CDDL
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Rule -> Rule -> Ordering) -> NonEmpty Rule -> NonEmpty Rule
forall a. (a -> a -> Ordering) -> NonEmpty a -> NonEmpty a
NE.sortBy (Name -> Name -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Name -> Name -> Ordering)
-> (Rule -> Name) -> Rule -> Rule -> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` Rule -> Name
ruleName) (NonEmpty Rule -> NonEmpty Rule)
-> (CDDL -> NonEmpty Rule) -> CDDL -> NonEmpty Rule
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CDDL -> NonEmpty Rule
cddlRules
cddlTopLevel :: CDDL -> NonEmpty TopLevel
cddlTopLevel :: CDDL -> NonEmpty TopLevel
cddlTopLevel (CDDL [Comment]
cmts Rule
cHead [TopLevel]
cTail) =
[TopLevel] -> NonEmpty TopLevel -> NonEmpty TopLevel
forall {a}. [a] -> NonEmpty a -> NonEmpty a
prependList (Comment -> TopLevel
TopLevelComment (Comment -> TopLevel) -> [Comment] -> [TopLevel]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Comment]
cmts) (NonEmpty TopLevel -> NonEmpty TopLevel)
-> NonEmpty TopLevel -> NonEmpty TopLevel
forall a b. (a -> b) -> a -> b
$ Rule -> TopLevel
TopLevelRule Rule
cHead TopLevel -> [TopLevel] -> NonEmpty TopLevel
forall a. a -> [a] -> NonEmpty a
:| [TopLevel]
cTail
where
prependList :: [a] -> NonEmpty a -> NonEmpty a
prependList [] NonEmpty a
l = NonEmpty a
l
prependList (a
x : [a]
xs) (a
y :| [a]
ys) = [a] -> NonEmpty a -> NonEmpty a
prependList [a]
xs (NonEmpty a -> NonEmpty a) -> NonEmpty a -> NonEmpty a
forall a b. (a -> b) -> a -> b
$ a
x a -> [a] -> NonEmpty a
forall a. a -> [a] -> NonEmpty a
:| (a
y a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
ys)
cddlRules :: CDDL -> NonEmpty Rule
cddlRules :: CDDL -> NonEmpty Rule
cddlRules (CDDL [Comment]
_ Rule
x [TopLevel]
tls) = Rule
x Rule -> [Rule] -> NonEmpty Rule
forall a. a -> [a] -> NonEmpty a
:| (TopLevel -> [Rule]) -> [TopLevel] -> [Rule]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap TopLevel -> [Rule]
getRule [TopLevel]
tls
where
getRule :: TopLevel -> [Rule]
getRule (TopLevelRule Rule
r) = [Rule
r]
getRule TopLevel
_ = [Rule]
forall a. Monoid a => a
mempty
fromRules :: NonEmpty Rule -> CDDL
fromRules :: NonEmpty Rule -> CDDL
fromRules (Rule
x :| [Rule]
xs) = [Comment] -> Rule -> [TopLevel] -> CDDL
CDDL [] Rule
x ([TopLevel] -> CDDL) -> [TopLevel] -> CDDL
forall a b. (a -> b) -> a -> b
$ Rule -> TopLevel
TopLevelRule (Rule -> TopLevel) -> [Rule] -> [TopLevel]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Rule]
xs
fromRule :: Rule -> CDDL
fromRule :: Rule -> CDDL
fromRule Rule
x = [Comment] -> Rule -> [TopLevel] -> CDDL
CDDL [] Rule
x []
instance Semigroup CDDL where
CDDL [Comment]
aComments Rule
aHead [TopLevel]
aTail <> :: CDDL -> CDDL -> CDDL
<> CDDL [Comment]
bComments Rule
bHead [TopLevel]
bTail =
[Comment] -> Rule -> [TopLevel] -> CDDL
CDDL [Comment]
aComments Rule
aHead ([TopLevel] -> CDDL) -> [TopLevel] -> CDDL
forall a b. (a -> b) -> a -> b
$
[TopLevel]
aTail [TopLevel] -> [TopLevel] -> [TopLevel]
forall a. Semigroup a => a -> a -> a
<> (Comment -> TopLevel) -> [Comment] -> [TopLevel]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Comment -> TopLevel
TopLevelComment [Comment]
bComments [TopLevel] -> [TopLevel] -> [TopLevel]
forall a. Semigroup a => a -> a -> a
<> (Rule -> TopLevel
TopLevelRule Rule
bHead TopLevel -> [TopLevel] -> [TopLevel]
forall a. a -> [a] -> [a]
: [TopLevel]
bTail)
data TopLevel
= TopLevelRule Rule
| Comment
deriving (TopLevel -> TopLevel -> Bool
(TopLevel -> TopLevel -> Bool)
-> (TopLevel -> TopLevel -> Bool) -> Eq TopLevel
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TopLevel -> TopLevel -> Bool
== :: TopLevel -> TopLevel -> Bool
$c/= :: TopLevel -> TopLevel -> Bool
/= :: TopLevel -> TopLevel -> Bool
Eq, (forall x. TopLevel -> Rep TopLevel x)
-> (forall x. Rep TopLevel x -> TopLevel) -> Generic TopLevel
forall x. Rep TopLevel x -> TopLevel
forall x. TopLevel -> Rep TopLevel x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TopLevel -> Rep TopLevel x
from :: forall x. TopLevel -> Rep TopLevel x
$cto :: forall x. Rep TopLevel x -> TopLevel
to :: forall x. Rep TopLevel x -> TopLevel
Generic, Int -> TopLevel -> ShowS
[TopLevel] -> ShowS
TopLevel -> String
(Int -> TopLevel -> ShowS)
-> (TopLevel -> String) -> ([TopLevel] -> ShowS) -> Show TopLevel
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TopLevel -> ShowS
showsPrec :: Int -> TopLevel -> ShowS
$cshow :: TopLevel -> String
show :: TopLevel -> String
$cshowList :: [TopLevel] -> ShowS
showList :: [TopLevel] -> ShowS
Show, [TopLevel] -> Expr
TopLevel -> Expr
(TopLevel -> Expr) -> ([TopLevel] -> Expr) -> ToExpr TopLevel
forall a. (a -> Expr) -> ([a] -> Expr) -> ToExpr a
$ctoExpr :: TopLevel -> Expr
toExpr :: TopLevel -> Expr
$clistToExpr :: [TopLevel] -> Expr
listToExpr :: [TopLevel] -> Expr
ToExpr)
data Name = Name
{ Name -> Text
name :: T.Text
, :: Comment
}
deriving (Name -> Name -> Bool
(Name -> Name -> Bool) -> (Name -> Name -> Bool) -> Eq Name
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Name -> Name -> Bool
== :: Name -> Name -> Bool
$c/= :: Name -> Name -> Bool
/= :: Name -> Name -> Bool
Eq, (forall x. Name -> Rep Name x)
-> (forall x. Rep Name x -> Name) -> Generic Name
forall x. Rep Name x -> Name
forall x. Name -> Rep Name x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Name -> Rep Name x
from :: forall x. Name -> Rep Name x
$cto :: forall x. Rep Name x -> Name
to :: forall x. Rep Name x -> Name
Generic, Eq Name
Eq Name =>
(Name -> Name -> Ordering)
-> (Name -> Name -> Bool)
-> (Name -> Name -> Bool)
-> (Name -> Name -> Bool)
-> (Name -> Name -> Bool)
-> (Name -> Name -> Name)
-> (Name -> Name -> Name)
-> Ord Name
Name -> Name -> Bool
Name -> Name -> Ordering
Name -> Name -> Name
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 :: Name -> Name -> Ordering
compare :: Name -> Name -> Ordering
$c< :: Name -> Name -> Bool
< :: Name -> Name -> Bool
$c<= :: Name -> Name -> Bool
<= :: Name -> Name -> Bool
$c> :: Name -> Name -> Bool
> :: Name -> Name -> Bool
$c>= :: Name -> Name -> Bool
>= :: Name -> Name -> Bool
$cmax :: Name -> Name -> Name
max :: Name -> Name -> Name
$cmin :: Name -> Name -> Name
min :: Name -> Name -> Name
Ord, Int -> Name -> ShowS
[Name] -> ShowS
Name -> String
(Int -> Name -> ShowS)
-> (Name -> String) -> ([Name] -> ShowS) -> Show Name
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Name -> ShowS
showsPrec :: Int -> Name -> ShowS
$cshow :: Name -> String
show :: Name -> String
$cshowList :: [Name] -> ShowS
showList :: [Name] -> ShowS
Show)
deriving anyclass ([Name] -> Expr
Name -> Expr
(Name -> Expr) -> ([Name] -> Expr) -> ToExpr Name
forall a. (a -> Expr) -> ([a] -> Expr) -> ToExpr a
$ctoExpr :: Name -> Expr
toExpr :: Name -> Expr
$clistToExpr :: [Name] -> Expr
listToExpr :: [Name] -> Expr
ToExpr)
instance IsString Name where
fromString :: String -> Name
fromString String
x = Text -> Comment -> Name
Name (String -> Text
T.pack String
x) Comment
forall a. Monoid a => a
mempty
instance HasComment Name where
commentL :: Lens' Name Comment
commentL = (Name -> Comment)
-> (Name -> Comment -> Name) -> Lens' Name Comment
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Name -> Comment
nameComment (\Name
x Comment
y -> Name
x {nameComment = y})
instance CollectComments Name where
collectComments :: Name -> [Comment]
collectComments (Name Text
_ Comment
c) = [Comment
c]
instance Hashable Name
data Assign = AssignEq | AssignExt
deriving (Assign -> Assign -> Bool
(Assign -> Assign -> Bool)
-> (Assign -> Assign -> Bool) -> Eq Assign
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Assign -> Assign -> Bool
== :: Assign -> Assign -> Bool
$c/= :: Assign -> Assign -> Bool
/= :: Assign -> Assign -> Bool
Eq, (forall x. Assign -> Rep Assign x)
-> (forall x. Rep Assign x -> Assign) -> Generic Assign
forall x. Rep Assign x -> Assign
forall x. Assign -> Rep Assign x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Assign -> Rep Assign x
from :: forall x. Assign -> Rep Assign x
$cto :: forall x. Rep Assign x -> Assign
to :: forall x. Rep Assign x -> Assign
Generic, Int -> Assign -> ShowS
[Assign] -> ShowS
Assign -> String
(Int -> Assign -> ShowS)
-> (Assign -> String) -> ([Assign] -> ShowS) -> Show Assign
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Assign -> ShowS
showsPrec :: Int -> Assign -> ShowS
$cshow :: Assign -> String
show :: Assign -> String
$cshowList :: [Assign] -> ShowS
showList :: [Assign] -> ShowS
Show)
deriving anyclass ([Assign] -> Expr
Assign -> Expr
(Assign -> Expr) -> ([Assign] -> Expr) -> ToExpr Assign
forall a. (a -> Expr) -> ([a] -> Expr) -> ToExpr a
$ctoExpr :: Assign -> Expr
toExpr :: Assign -> Expr
$clistToExpr :: [Assign] -> Expr
listToExpr :: [Assign] -> Expr
ToExpr)
newtype GenericParam = GenericParam (NE.NonEmpty Name)
deriving (GenericParam -> GenericParam -> Bool
(GenericParam -> GenericParam -> Bool)
-> (GenericParam -> GenericParam -> Bool) -> Eq GenericParam
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GenericParam -> GenericParam -> Bool
== :: GenericParam -> GenericParam -> Bool
$c/= :: GenericParam -> GenericParam -> Bool
/= :: GenericParam -> GenericParam -> Bool
Eq, (forall x. GenericParam -> Rep GenericParam x)
-> (forall x. Rep GenericParam x -> GenericParam)
-> Generic GenericParam
forall x. Rep GenericParam x -> GenericParam
forall x. GenericParam -> Rep GenericParam x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GenericParam -> Rep GenericParam x
from :: forall x. GenericParam -> Rep GenericParam x
$cto :: forall x. Rep GenericParam x -> GenericParam
to :: forall x. Rep GenericParam x -> GenericParam
Generic, Int -> GenericParam -> ShowS
[GenericParam] -> ShowS
GenericParam -> String
(Int -> GenericParam -> ShowS)
-> (GenericParam -> String)
-> ([GenericParam] -> ShowS)
-> Show GenericParam
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GenericParam -> ShowS
showsPrec :: Int -> GenericParam -> ShowS
$cshow :: GenericParam -> String
show :: GenericParam -> String
$cshowList :: [GenericParam] -> ShowS
showList :: [GenericParam] -> ShowS
Show)
deriving newtype (NonEmpty GenericParam -> GenericParam
GenericParam -> GenericParam -> GenericParam
(GenericParam -> GenericParam -> GenericParam)
-> (NonEmpty GenericParam -> GenericParam)
-> (forall b. Integral b => b -> GenericParam -> GenericParam)
-> Semigroup GenericParam
forall b. Integral b => b -> GenericParam -> GenericParam
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
$c<> :: GenericParam -> GenericParam -> GenericParam
<> :: GenericParam -> GenericParam -> GenericParam
$csconcat :: NonEmpty GenericParam -> GenericParam
sconcat :: NonEmpty GenericParam -> GenericParam
$cstimes :: forall b. Integral b => b -> GenericParam -> GenericParam
stimes :: forall b. Integral b => b -> GenericParam -> GenericParam
Semigroup)
deriving anyclass ([GenericParam] -> Expr
GenericParam -> Expr
(GenericParam -> Expr)
-> ([GenericParam] -> Expr) -> ToExpr GenericParam
forall a. (a -> Expr) -> ([a] -> Expr) -> ToExpr a
$ctoExpr :: GenericParam -> Expr
toExpr :: GenericParam -> Expr
$clistToExpr :: [GenericParam] -> Expr
listToExpr :: [GenericParam] -> Expr
ToExpr)
newtype GenericArg = GenericArg (NE.NonEmpty Type1)
deriving (GenericArg -> GenericArg -> Bool
(GenericArg -> GenericArg -> Bool)
-> (GenericArg -> GenericArg -> Bool) -> Eq GenericArg
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GenericArg -> GenericArg -> Bool
== :: GenericArg -> GenericArg -> Bool
$c/= :: GenericArg -> GenericArg -> Bool
/= :: GenericArg -> GenericArg -> Bool
Eq, (forall x. GenericArg -> Rep GenericArg x)
-> (forall x. Rep GenericArg x -> GenericArg) -> Generic GenericArg
forall x. Rep GenericArg x -> GenericArg
forall x. GenericArg -> Rep GenericArg x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GenericArg -> Rep GenericArg x
from :: forall x. GenericArg -> Rep GenericArg x
$cto :: forall x. Rep GenericArg x -> GenericArg
to :: forall x. Rep GenericArg x -> GenericArg
Generic, Int -> GenericArg -> ShowS
[GenericArg] -> ShowS
GenericArg -> String
(Int -> GenericArg -> ShowS)
-> (GenericArg -> String)
-> ([GenericArg] -> ShowS)
-> Show GenericArg
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GenericArg -> ShowS
showsPrec :: Int -> GenericArg -> ShowS
$cshow :: GenericArg -> String
show :: GenericArg -> String
$cshowList :: [GenericArg] -> ShowS
showList :: [GenericArg] -> ShowS
Show)
deriving newtype (NonEmpty GenericArg -> GenericArg
GenericArg -> GenericArg -> GenericArg
(GenericArg -> GenericArg -> GenericArg)
-> (NonEmpty GenericArg -> GenericArg)
-> (forall b. Integral b => b -> GenericArg -> GenericArg)
-> Semigroup GenericArg
forall b. Integral b => b -> GenericArg -> GenericArg
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
$c<> :: GenericArg -> GenericArg -> GenericArg
<> :: GenericArg -> GenericArg -> GenericArg
$csconcat :: NonEmpty GenericArg -> GenericArg
sconcat :: NonEmpty GenericArg -> GenericArg
$cstimes :: forall b. Integral b => b -> GenericArg -> GenericArg
stimes :: forall b. Integral b => b -> GenericArg -> GenericArg
Semigroup)
deriving anyclass ([GenericArg] -> Expr
GenericArg -> Expr
(GenericArg -> Expr) -> ([GenericArg] -> Expr) -> ToExpr GenericArg
forall a. (a -> Expr) -> ([a] -> Expr) -> ToExpr a
$ctoExpr :: GenericArg -> Expr
toExpr :: GenericArg -> Expr
$clistToExpr :: [GenericArg] -> Expr
listToExpr :: [GenericArg] -> Expr
ToExpr)
instance CollectComments GenericArg
data Rule = Rule
{ Rule -> Name
ruleName :: Name
, Rule -> Maybe GenericParam
ruleGenParam :: Maybe GenericParam
, Rule -> Assign
ruleAssign :: Assign
, Rule -> TypeOrGroup
ruleTerm :: TypeOrGroup
, :: Comment
}
deriving (Rule -> Rule -> Bool
(Rule -> Rule -> Bool) -> (Rule -> Rule -> Bool) -> Eq Rule
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Rule -> Rule -> Bool
== :: Rule -> Rule -> Bool
$c/= :: Rule -> Rule -> Bool
/= :: Rule -> Rule -> Bool
Eq, (forall x. Rule -> Rep Rule x)
-> (forall x. Rep Rule x -> Rule) -> Generic Rule
forall x. Rep Rule x -> Rule
forall x. Rule -> Rep Rule x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Rule -> Rep Rule x
from :: forall x. Rule -> Rep Rule x
$cto :: forall x. Rep Rule x -> Rule
to :: forall x. Rep Rule x -> Rule
Generic, Int -> Rule -> ShowS
[Rule] -> ShowS
Rule -> String
(Int -> Rule -> ShowS)
-> (Rule -> String) -> ([Rule] -> ShowS) -> Show Rule
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Rule -> ShowS
showsPrec :: Int -> Rule -> ShowS
$cshow :: Rule -> String
show :: Rule -> String
$cshowList :: [Rule] -> ShowS
showList :: [Rule] -> ShowS
Show)
deriving anyclass ([Rule] -> Expr
Rule -> Expr
(Rule -> Expr) -> ([Rule] -> Expr) -> ToExpr Rule
forall a. (a -> Expr) -> ([a] -> Expr) -> ToExpr a
$ctoExpr :: Rule -> Expr
toExpr :: Rule -> Expr
$clistToExpr :: [Rule] -> Expr
listToExpr :: [Rule] -> Expr
ToExpr)
instance HasComment Rule where
commentL :: Lens' Rule Comment
commentL = (Rule -> Comment)
-> (Rule -> Comment -> Rule) -> Lens' Rule Comment
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Rule -> Comment
ruleComment (\Rule
x Comment
y -> Rule
x {ruleComment = y})
compareRuleName :: Rule -> Rule -> Ordering
compareRuleName :: Rule -> Rule -> Ordering
compareRuleName = Name -> Name -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Name -> Name -> Ordering)
-> (Rule -> Name) -> Rule -> Rule -> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` Rule -> Name
ruleName
data RangeBound = ClOpen | Closed
deriving (RangeBound -> RangeBound -> Bool
(RangeBound -> RangeBound -> Bool)
-> (RangeBound -> RangeBound -> Bool) -> Eq RangeBound
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RangeBound -> RangeBound -> Bool
== :: RangeBound -> RangeBound -> Bool
$c/= :: RangeBound -> RangeBound -> Bool
/= :: RangeBound -> RangeBound -> Bool
Eq, (forall x. RangeBound -> Rep RangeBound x)
-> (forall x. Rep RangeBound x -> RangeBound) -> Generic RangeBound
forall x. Rep RangeBound x -> RangeBound
forall x. RangeBound -> Rep RangeBound x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RangeBound -> Rep RangeBound x
from :: forall x. RangeBound -> Rep RangeBound x
$cto :: forall x. Rep RangeBound x -> RangeBound
to :: forall x. Rep RangeBound x -> RangeBound
Generic, Int -> RangeBound -> ShowS
[RangeBound] -> ShowS
RangeBound -> String
(Int -> RangeBound -> ShowS)
-> (RangeBound -> String)
-> ([RangeBound] -> ShowS)
-> Show RangeBound
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RangeBound -> ShowS
showsPrec :: Int -> RangeBound -> ShowS
$cshow :: RangeBound -> String
show :: RangeBound -> String
$cshowList :: [RangeBound] -> ShowS
showList :: [RangeBound] -> ShowS
Show)
deriving anyclass ([RangeBound] -> Expr
RangeBound -> Expr
(RangeBound -> Expr) -> ([RangeBound] -> Expr) -> ToExpr RangeBound
forall a. (a -> Expr) -> ([a] -> Expr) -> ToExpr a
$ctoExpr :: RangeBound -> Expr
toExpr :: RangeBound -> Expr
$clistToExpr :: [RangeBound] -> Expr
listToExpr :: [RangeBound] -> Expr
ToExpr)
instance Hashable RangeBound
data TyOp = RangeOp RangeBound | CtrlOp CtlOp
deriving (TyOp -> TyOp -> Bool
(TyOp -> TyOp -> Bool) -> (TyOp -> TyOp -> Bool) -> Eq TyOp
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TyOp -> TyOp -> Bool
== :: TyOp -> TyOp -> Bool
$c/= :: TyOp -> TyOp -> Bool
/= :: TyOp -> TyOp -> Bool
Eq, (forall x. TyOp -> Rep TyOp x)
-> (forall x. Rep TyOp x -> TyOp) -> Generic TyOp
forall x. Rep TyOp x -> TyOp
forall x. TyOp -> Rep TyOp x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TyOp -> Rep TyOp x
from :: forall x. TyOp -> Rep TyOp x
$cto :: forall x. Rep TyOp x -> TyOp
to :: forall x. Rep TyOp x -> TyOp
Generic, Int -> TyOp -> ShowS
[TyOp] -> ShowS
TyOp -> String
(Int -> TyOp -> ShowS)
-> (TyOp -> String) -> ([TyOp] -> ShowS) -> Show TyOp
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TyOp -> ShowS
showsPrec :: Int -> TyOp -> ShowS
$cshow :: TyOp -> String
show :: TyOp -> String
$cshowList :: [TyOp] -> ShowS
showList :: [TyOp] -> ShowS
Show)
deriving anyclass ([TyOp] -> Expr
TyOp -> Expr
(TyOp -> Expr) -> ([TyOp] -> Expr) -> ToExpr TyOp
forall a. (a -> Expr) -> ([a] -> Expr) -> ToExpr a
$ctoExpr :: TyOp -> Expr
toExpr :: TyOp -> Expr
$clistToExpr :: [TyOp] -> Expr
listToExpr :: [TyOp] -> Expr
ToExpr)
data TypeOrGroup = TOGType Type0 | TOGGroup GroupEntry
deriving (TypeOrGroup -> TypeOrGroup -> Bool
(TypeOrGroup -> TypeOrGroup -> Bool)
-> (TypeOrGroup -> TypeOrGroup -> Bool) -> Eq TypeOrGroup
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TypeOrGroup -> TypeOrGroup -> Bool
== :: TypeOrGroup -> TypeOrGroup -> Bool
$c/= :: TypeOrGroup -> TypeOrGroup -> Bool
/= :: TypeOrGroup -> TypeOrGroup -> Bool
Eq, (forall x. TypeOrGroup -> Rep TypeOrGroup x)
-> (forall x. Rep TypeOrGroup x -> TypeOrGroup)
-> Generic TypeOrGroup
forall x. Rep TypeOrGroup x -> TypeOrGroup
forall x. TypeOrGroup -> Rep TypeOrGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. TypeOrGroup -> Rep TypeOrGroup x
from :: forall x. TypeOrGroup -> Rep TypeOrGroup x
$cto :: forall x. Rep TypeOrGroup x -> TypeOrGroup
to :: forall x. Rep TypeOrGroup x -> TypeOrGroup
Generic, Int -> TypeOrGroup -> ShowS
[TypeOrGroup] -> ShowS
TypeOrGroup -> String
(Int -> TypeOrGroup -> ShowS)
-> (TypeOrGroup -> String)
-> ([TypeOrGroup] -> ShowS)
-> Show TypeOrGroup
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TypeOrGroup -> ShowS
showsPrec :: Int -> TypeOrGroup -> ShowS
$cshow :: TypeOrGroup -> String
show :: TypeOrGroup -> String
$cshowList :: [TypeOrGroup] -> ShowS
showList :: [TypeOrGroup] -> ShowS
Show)
deriving anyclass ([TypeOrGroup] -> Expr
TypeOrGroup -> Expr
(TypeOrGroup -> Expr)
-> ([TypeOrGroup] -> Expr) -> ToExpr TypeOrGroup
forall a. (a -> Expr) -> ([a] -> Expr) -> ToExpr a
$ctoExpr :: TypeOrGroup -> Expr
toExpr :: TypeOrGroup -> Expr
$clistToExpr :: [TypeOrGroup] -> Expr
listToExpr :: [TypeOrGroup] -> Expr
ToExpr)
instance CollectComments TypeOrGroup
unwrap :: TypeOrGroup -> Maybe Group
unwrap :: TypeOrGroup -> Maybe Group
unwrap (TOGType (Type0 (Type1 Type2
t2 Maybe (TyOp, Type2)
Nothing Comment
_ NE.:| []))) = case Type2
t2 of
T2Map Group
g -> Group -> Maybe Group
forall a. a -> Maybe a
Just Group
g
T2Array Group
g -> Group -> Maybe Group
forall a. a -> Maybe a
Just Group
g
Type2
_ -> Maybe Group
forall a. Maybe a
Nothing
unwrap TypeOrGroup
_ = Maybe Group
forall a. Maybe a
Nothing
newtype Type0 = Type0 {Type0 -> NonEmpty Type1
t0Type1 :: NE.NonEmpty Type1}
deriving (Type0 -> Type0 -> Bool
(Type0 -> Type0 -> Bool) -> (Type0 -> Type0 -> Bool) -> Eq Type0
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Type0 -> Type0 -> Bool
== :: Type0 -> Type0 -> Bool
$c/= :: Type0 -> Type0 -> Bool
/= :: Type0 -> Type0 -> Bool
Eq, (forall x. Type0 -> Rep Type0 x)
-> (forall x. Rep Type0 x -> Type0) -> Generic Type0
forall x. Rep Type0 x -> Type0
forall x. Type0 -> Rep Type0 x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Type0 -> Rep Type0 x
from :: forall x. Type0 -> Rep Type0 x
$cto :: forall x. Rep Type0 x -> Type0
to :: forall x. Rep Type0 x -> Type0
Generic, Int -> Type0 -> ShowS
[Type0] -> ShowS
Type0 -> String
(Int -> Type0 -> ShowS)
-> (Type0 -> String) -> ([Type0] -> ShowS) -> Show Type0
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Type0 -> ShowS
showsPrec :: Int -> Type0 -> ShowS
$cshow :: Type0 -> String
show :: Type0 -> String
$cshowList :: [Type0] -> ShowS
showList :: [Type0] -> ShowS
Show)
deriving newtype (NonEmpty Type0 -> Type0
Type0 -> Type0 -> Type0
(Type0 -> Type0 -> Type0)
-> (NonEmpty Type0 -> Type0)
-> (forall b. Integral b => b -> Type0 -> Type0)
-> Semigroup Type0
forall b. Integral b => b -> Type0 -> Type0
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
$c<> :: Type0 -> Type0 -> Type0
<> :: Type0 -> Type0 -> Type0
$csconcat :: NonEmpty Type0 -> Type0
sconcat :: NonEmpty Type0 -> Type0
$cstimes :: forall b. Integral b => b -> Type0 -> Type0
stimes :: forall b. Integral b => b -> Type0 -> Type0
Semigroup)
deriving anyclass ([Type0] -> Expr
Type0 -> Expr
(Type0 -> Expr) -> ([Type0] -> Expr) -> ToExpr Type0
forall a. (a -> Expr) -> ([a] -> Expr) -> ToExpr a
$ctoExpr :: Type0 -> Expr
toExpr :: Type0 -> Expr
$clistToExpr :: [Type0] -> Expr
listToExpr :: [Type0] -> Expr
ToExpr)
instance HasComment Type0 where
commentL :: Lens' Type0 Comment
commentL = (Type0 -> Comment)
-> (Type0 -> Comment -> Type0) -> Lens' Type0 Comment
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens (Optic' A_Lens NoIx (NonEmpty Type1) Comment
-> NonEmpty Type1 -> Comment
forall k (is :: IxList) s a.
Is k A_Getter =>
Optic' k is s a -> s -> a
view Optic' A_Lens NoIx (NonEmpty Type1) Comment
forall a. HasComment a => Lens' a Comment
commentL (NonEmpty Type1 -> Comment)
-> (Type0 -> NonEmpty Type1) -> Type0 -> Comment
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Type0 -> NonEmpty Type1
t0Type1) (\(Type0 NonEmpty Type1
x) Comment
y -> NonEmpty Type1 -> Type0
Type0 (NonEmpty Type1 -> Type0) -> NonEmpty Type1 -> Type0
forall a b. (a -> b) -> a -> b
$ NonEmpty Type1
x NonEmpty Type1
-> (NonEmpty Type1 -> NonEmpty Type1) -> NonEmpty Type1
forall a b. a -> (a -> b) -> b
& Optic' A_Lens NoIx (NonEmpty Type1) Comment
forall a. HasComment a => Lens' a Comment
commentL Optic' A_Lens NoIx (NonEmpty Type1) Comment
-> Comment -> NonEmpty Type1 -> NonEmpty Type1
forall k (is :: IxList) s t a b.
Is k A_Setter =>
Optic k is s t a b -> b -> s -> t
.~ Comment
y)
instance CollectComments Type0
data Type1 = Type1
{ Type1 -> Type2
t1Main :: Type2
, Type1 -> Maybe (TyOp, Type2)
t1TyOp :: Maybe (TyOp, Type2)
, :: Comment
}
deriving (Type1 -> Type1 -> Bool
(Type1 -> Type1 -> Bool) -> (Type1 -> Type1 -> Bool) -> Eq Type1
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Type1 -> Type1 -> Bool
== :: Type1 -> Type1 -> Bool
$c/= :: Type1 -> Type1 -> Bool
/= :: Type1 -> Type1 -> Bool
Eq, (forall x. Type1 -> Rep Type1 x)
-> (forall x. Rep Type1 x -> Type1) -> Generic Type1
forall x. Rep Type1 x -> Type1
forall x. Type1 -> Rep Type1 x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Type1 -> Rep Type1 x
from :: forall x. Type1 -> Rep Type1 x
$cto :: forall x. Rep Type1 x -> Type1
to :: forall x. Rep Type1 x -> Type1
Generic, Int -> Type1 -> ShowS
[Type1] -> ShowS
Type1 -> String
(Int -> Type1 -> ShowS)
-> (Type1 -> String) -> ([Type1] -> ShowS) -> Show Type1
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Type1 -> ShowS
showsPrec :: Int -> Type1 -> ShowS
$cshow :: Type1 -> String
show :: Type1 -> String
$cshowList :: [Type1] -> ShowS
showList :: [Type1] -> ShowS
Show)
deriving anyclass ([Type1] -> Expr
Type1 -> Expr
(Type1 -> Expr) -> ([Type1] -> Expr) -> ToExpr Type1
forall a. (a -> Expr) -> ([a] -> Expr) -> ToExpr a
$ctoExpr :: Type1 -> Expr
toExpr :: Type1 -> Expr
$clistToExpr :: [Type1] -> Expr
listToExpr :: [Type1] -> Expr
ToExpr, Type1
Type1 -> Default Type1
forall a. a -> Default a
$cdef :: Type1
def :: Type1
Default)
instance HasComment Type1 where
commentL :: Lens' Type1 Comment
commentL = (Type1 -> Comment)
-> (Type1 -> Comment -> Type1) -> Lens' Type1 Comment
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Type1 -> Comment
t1Comment (\Type1
x Comment
y -> Type1
x {t1Comment = y})
instance CollectComments Type1 where
collectComments :: Type1 -> [Comment]
collectComments (Type1 Type2
m Maybe (TyOp, Type2)
tyOp Comment
c) = Comment
c Comment -> [Comment] -> [Comment]
forall a. a -> [a] -> [a]
: Type2 -> [Comment]
forall a. CollectComments a => a -> [Comment]
collectComments Type2
m [Comment] -> [Comment] -> [Comment]
forall a. Semigroup a => a -> a -> a
<> Maybe Type2 -> [Comment]
forall a. CollectComments a => a -> [Comment]
collectComments (((TyOp, Type2) -> Type2) -> Maybe (TyOp, Type2) -> Maybe Type2
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (TyOp, Type2) -> Type2
forall a b. (a, b) -> b
snd Maybe (TyOp, Type2)
tyOp)
data Type2
=
T2Value Value
|
T2Name Name (Maybe GenericArg)
|
T2Group Type0
|
T2Map Group
|
T2Array Group
|
T2Unwrapped Name (Maybe GenericArg)
|
T2Enum Group
| T2EnumRef Name (Maybe GenericArg)
|
T2Tag (Maybe Word64) Type0
|
T2DataItem Word8 (Maybe Word64)
|
T2Any
deriving (Type2 -> Type2 -> Bool
(Type2 -> Type2 -> Bool) -> (Type2 -> Type2 -> Bool) -> Eq Type2
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Type2 -> Type2 -> Bool
== :: Type2 -> Type2 -> Bool
$c/= :: Type2 -> Type2 -> Bool
/= :: Type2 -> Type2 -> Bool
Eq, (forall x. Type2 -> Rep Type2 x)
-> (forall x. Rep Type2 x -> Type2) -> Generic Type2
forall x. Rep Type2 x -> Type2
forall x. Type2 -> Rep Type2 x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Type2 -> Rep Type2 x
from :: forall x. Type2 -> Rep Type2 x
$cto :: forall x. Rep Type2 x -> Type2
to :: forall x. Rep Type2 x -> Type2
Generic, Int -> Type2 -> ShowS
[Type2] -> ShowS
Type2 -> String
(Int -> Type2 -> ShowS)
-> (Type2 -> String) -> ([Type2] -> ShowS) -> Show Type2
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Type2 -> ShowS
showsPrec :: Int -> Type2 -> ShowS
$cshow :: Type2 -> String
show :: Type2 -> String
$cshowList :: [Type2] -> ShowS
showList :: [Type2] -> ShowS
Show, Type2
Type2 -> Default Type2
forall a. a -> Default a
$cdef :: Type2
def :: Type2
Default)
deriving anyclass ([Type2] -> Expr
Type2 -> Expr
(Type2 -> Expr) -> ([Type2] -> Expr) -> ToExpr Type2
forall a. (a -> Expr) -> ([a] -> Expr) -> ToExpr a
$ctoExpr :: Type2 -> Expr
toExpr :: Type2 -> Expr
$clistToExpr :: [Type2] -> Expr
listToExpr :: [Type2] -> Expr
ToExpr)
instance CollectComments Type2
data OccurrenceIndicator
= OIOptional
| OIZeroOrMore
| OIOneOrMore
| OIBounded (Maybe Word64) (Maybe Word64)
deriving (OccurrenceIndicator -> OccurrenceIndicator -> Bool
(OccurrenceIndicator -> OccurrenceIndicator -> Bool)
-> (OccurrenceIndicator -> OccurrenceIndicator -> Bool)
-> Eq OccurrenceIndicator
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OccurrenceIndicator -> OccurrenceIndicator -> Bool
== :: OccurrenceIndicator -> OccurrenceIndicator -> Bool
$c/= :: OccurrenceIndicator -> OccurrenceIndicator -> Bool
/= :: OccurrenceIndicator -> OccurrenceIndicator -> Bool
Eq, (forall x. OccurrenceIndicator -> Rep OccurrenceIndicator x)
-> (forall x. Rep OccurrenceIndicator x -> OccurrenceIndicator)
-> Generic OccurrenceIndicator
forall x. Rep OccurrenceIndicator x -> OccurrenceIndicator
forall x. OccurrenceIndicator -> Rep OccurrenceIndicator x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. OccurrenceIndicator -> Rep OccurrenceIndicator x
from :: forall x. OccurrenceIndicator -> Rep OccurrenceIndicator x
$cto :: forall x. Rep OccurrenceIndicator x -> OccurrenceIndicator
to :: forall x. Rep OccurrenceIndicator x -> OccurrenceIndicator
Generic, Int -> OccurrenceIndicator -> ShowS
[OccurrenceIndicator] -> ShowS
OccurrenceIndicator -> String
(Int -> OccurrenceIndicator -> ShowS)
-> (OccurrenceIndicator -> String)
-> ([OccurrenceIndicator] -> ShowS)
-> Show OccurrenceIndicator
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OccurrenceIndicator -> ShowS
showsPrec :: Int -> OccurrenceIndicator -> ShowS
$cshow :: OccurrenceIndicator -> String
show :: OccurrenceIndicator -> String
$cshowList :: [OccurrenceIndicator] -> ShowS
showList :: [OccurrenceIndicator] -> ShowS
Show)
deriving anyclass ([OccurrenceIndicator] -> Expr
OccurrenceIndicator -> Expr
(OccurrenceIndicator -> Expr)
-> ([OccurrenceIndicator] -> Expr) -> ToExpr OccurrenceIndicator
forall a. (a -> Expr) -> ([a] -> Expr) -> ToExpr a
$ctoExpr :: OccurrenceIndicator -> Expr
toExpr :: OccurrenceIndicator -> Expr
$clistToExpr :: [OccurrenceIndicator] -> Expr
listToExpr :: [OccurrenceIndicator] -> Expr
ToExpr)
instance Hashable OccurrenceIndicator
newtype Group = Group {Group -> NonEmpty GrpChoice
unGroup :: NE.NonEmpty GrpChoice}
deriving (Group -> Group -> Bool
(Group -> Group -> Bool) -> (Group -> Group -> Bool) -> Eq Group
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Group -> Group -> Bool
== :: Group -> Group -> Bool
$c/= :: Group -> Group -> Bool
/= :: Group -> Group -> Bool
Eq, (forall x. Group -> Rep Group x)
-> (forall x. Rep Group x -> Group) -> Generic Group
forall x. Rep Group x -> Group
forall x. Group -> Rep Group x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Group -> Rep Group x
from :: forall x. Group -> Rep Group x
$cto :: forall x. Rep Group x -> Group
to :: forall x. Rep Group x -> Group
Generic, Int -> Group -> ShowS
[Group] -> ShowS
Group -> String
(Int -> Group -> ShowS)
-> (Group -> String) -> ([Group] -> ShowS) -> Show Group
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Group -> ShowS
showsPrec :: Int -> Group -> ShowS
$cshow :: Group -> String
show :: Group -> String
$cshowList :: [Group] -> ShowS
showList :: [Group] -> ShowS
Show)
deriving newtype (NonEmpty Group -> Group
Group -> Group -> Group
(Group -> Group -> Group)
-> (NonEmpty Group -> Group)
-> (forall b. Integral b => b -> Group -> Group)
-> Semigroup Group
forall b. Integral b => b -> Group -> Group
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
$c<> :: Group -> Group -> Group
<> :: Group -> Group -> Group
$csconcat :: NonEmpty Group -> Group
sconcat :: NonEmpty Group -> Group
$cstimes :: forall b. Integral b => b -> Group -> Group
stimes :: forall b. Integral b => b -> Group -> Group
Semigroup)
deriving anyclass ([Group] -> Expr
Group -> Expr
(Group -> Expr) -> ([Group] -> Expr) -> ToExpr Group
forall a. (a -> Expr) -> ([a] -> Expr) -> ToExpr a
$ctoExpr :: Group -> Expr
toExpr :: Group -> Expr
$clistToExpr :: [Group] -> Expr
listToExpr :: [Group] -> Expr
ToExpr)
instance HasComment Group where
commentL :: Lens' Group Comment
commentL = (Group -> NonEmpty GrpChoice)
-> (Group -> NonEmpty GrpChoice -> Group)
-> Lens Group Group (NonEmpty GrpChoice) (NonEmpty GrpChoice)
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens Group -> NonEmpty GrpChoice
unGroup (\Group
x NonEmpty GrpChoice
y -> Group
x {unGroup = y}) Lens Group Group (NonEmpty GrpChoice) (NonEmpty GrpChoice)
-> Optic
A_Lens
NoIx
(NonEmpty GrpChoice)
(NonEmpty GrpChoice)
Comment
Comment
-> Lens' Group Comment
forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% Optic
A_Lens
NoIx
(NonEmpty GrpChoice)
(NonEmpty GrpChoice)
Comment
Comment
forall a. HasComment a => Lens' a Comment
commentL
instance CollectComments Group where
collectComments :: Group -> [Comment]
collectComments (Group NonEmpty GrpChoice
xs) = (GrpChoice -> [Comment]) -> NonEmpty GrpChoice -> [Comment]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap GrpChoice -> [Comment]
forall a. CollectComments a => a -> [Comment]
collectComments NonEmpty GrpChoice
xs
data GrpChoice = GrpChoice
{ GrpChoice -> [GroupEntry]
gcGroupEntries :: [GroupEntry]
, :: Comment
}
deriving (GrpChoice -> GrpChoice -> Bool
(GrpChoice -> GrpChoice -> Bool)
-> (GrpChoice -> GrpChoice -> Bool) -> Eq GrpChoice
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GrpChoice -> GrpChoice -> Bool
== :: GrpChoice -> GrpChoice -> Bool
$c/= :: GrpChoice -> GrpChoice -> Bool
/= :: GrpChoice -> GrpChoice -> Bool
Eq, (forall x. GrpChoice -> Rep GrpChoice x)
-> (forall x. Rep GrpChoice x -> GrpChoice) -> Generic GrpChoice
forall x. Rep GrpChoice x -> GrpChoice
forall x. GrpChoice -> Rep GrpChoice x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GrpChoice -> Rep GrpChoice x
from :: forall x. GrpChoice -> Rep GrpChoice x
$cto :: forall x. Rep GrpChoice x -> GrpChoice
to :: forall x. Rep GrpChoice x -> GrpChoice
Generic, Int -> GrpChoice -> ShowS
[GrpChoice] -> ShowS
GrpChoice -> String
(Int -> GrpChoice -> ShowS)
-> (GrpChoice -> String)
-> ([GrpChoice] -> ShowS)
-> Show GrpChoice
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GrpChoice -> ShowS
showsPrec :: Int -> GrpChoice -> ShowS
$cshow :: GrpChoice -> String
show :: GrpChoice -> String
$cshowList :: [GrpChoice] -> ShowS
showList :: [GrpChoice] -> ShowS
Show)
deriving anyclass ([GrpChoice] -> Expr
GrpChoice -> Expr
(GrpChoice -> Expr) -> ([GrpChoice] -> Expr) -> ToExpr GrpChoice
forall a. (a -> Expr) -> ([a] -> Expr) -> ToExpr a
$ctoExpr :: GrpChoice -> Expr
toExpr :: GrpChoice -> Expr
$clistToExpr :: [GrpChoice] -> Expr
listToExpr :: [GrpChoice] -> Expr
ToExpr)
instance HasComment GrpChoice where
commentL :: Lens' GrpChoice Comment
commentL = (GrpChoice -> Comment)
-> (GrpChoice -> Comment -> GrpChoice) -> Lens' GrpChoice Comment
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens GrpChoice -> Comment
gcComment (\GrpChoice
x Comment
y -> GrpChoice
x {gcComment = y})
instance CollectComments GrpChoice where
collectComments :: GrpChoice -> [Comment]
collectComments (GrpChoice [GroupEntry]
ges Comment
c) = Comment
c Comment -> [Comment] -> [Comment]
forall a. a -> [a] -> [a]
: (GroupEntry -> [Comment]) -> [GroupEntry] -> [Comment]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap GroupEntry -> [Comment]
forall a. CollectComments a => a -> [Comment]
collectComments [GroupEntry]
ges
data GroupEntry = GroupEntry
{ GroupEntry -> Maybe OccurrenceIndicator
geOccurrenceIndicator :: Maybe OccurrenceIndicator
, :: Comment
, GroupEntry -> GroupEntryVariant
geVariant :: GroupEntryVariant
}
deriving (GroupEntry -> GroupEntry -> Bool
(GroupEntry -> GroupEntry -> Bool)
-> (GroupEntry -> GroupEntry -> Bool) -> Eq GroupEntry
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GroupEntry -> GroupEntry -> Bool
== :: GroupEntry -> GroupEntry -> Bool
$c/= :: GroupEntry -> GroupEntry -> Bool
/= :: GroupEntry -> GroupEntry -> Bool
Eq, Int -> GroupEntry -> ShowS
[GroupEntry] -> ShowS
GroupEntry -> String
(Int -> GroupEntry -> ShowS)
-> (GroupEntry -> String)
-> ([GroupEntry] -> ShowS)
-> Show GroupEntry
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GroupEntry -> ShowS
showsPrec :: Int -> GroupEntry -> ShowS
$cshow :: GroupEntry -> String
show :: GroupEntry -> String
$cshowList :: [GroupEntry] -> ShowS
showList :: [GroupEntry] -> ShowS
Show, (forall x. GroupEntry -> Rep GroupEntry x)
-> (forall x. Rep GroupEntry x -> GroupEntry) -> Generic GroupEntry
forall x. Rep GroupEntry x -> GroupEntry
forall x. GroupEntry -> Rep GroupEntry x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GroupEntry -> Rep GroupEntry x
from :: forall x. GroupEntry -> Rep GroupEntry x
$cto :: forall x. Rep GroupEntry x -> GroupEntry
to :: forall x. Rep GroupEntry x -> GroupEntry
Generic, [GroupEntry] -> Expr
GroupEntry -> Expr
(GroupEntry -> Expr) -> ([GroupEntry] -> Expr) -> ToExpr GroupEntry
forall a. (a -> Expr) -> ([a] -> Expr) -> ToExpr a
$ctoExpr :: GroupEntry -> Expr
toExpr :: GroupEntry -> Expr
$clistToExpr :: [GroupEntry] -> Expr
listToExpr :: [GroupEntry] -> Expr
ToExpr)
instance CollectComments GroupEntry where
collectComments :: GroupEntry -> [Comment]
collectComments (GroupEntry Maybe OccurrenceIndicator
_ Comment
c GroupEntryVariant
x) = Comment
c Comment -> [Comment] -> [Comment]
forall a. a -> [a] -> [a]
: GroupEntryVariant -> [Comment]
forall a. CollectComments a => a -> [Comment]
collectComments GroupEntryVariant
x
data GroupEntryVariant
= GEType (Maybe MemberKey) Type0
| GERef Name (Maybe GenericArg)
| GEGroup Group
deriving (GroupEntryVariant -> GroupEntryVariant -> Bool
(GroupEntryVariant -> GroupEntryVariant -> Bool)
-> (GroupEntryVariant -> GroupEntryVariant -> Bool)
-> Eq GroupEntryVariant
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GroupEntryVariant -> GroupEntryVariant -> Bool
== :: GroupEntryVariant -> GroupEntryVariant -> Bool
$c/= :: GroupEntryVariant -> GroupEntryVariant -> Bool
/= :: GroupEntryVariant -> GroupEntryVariant -> Bool
Eq, Int -> GroupEntryVariant -> ShowS
[GroupEntryVariant] -> ShowS
GroupEntryVariant -> String
(Int -> GroupEntryVariant -> ShowS)
-> (GroupEntryVariant -> String)
-> ([GroupEntryVariant] -> ShowS)
-> Show GroupEntryVariant
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GroupEntryVariant -> ShowS
showsPrec :: Int -> GroupEntryVariant -> ShowS
$cshow :: GroupEntryVariant -> String
show :: GroupEntryVariant -> String
$cshowList :: [GroupEntryVariant] -> ShowS
showList :: [GroupEntryVariant] -> ShowS
Show, (forall x. GroupEntryVariant -> Rep GroupEntryVariant x)
-> (forall x. Rep GroupEntryVariant x -> GroupEntryVariant)
-> Generic GroupEntryVariant
forall x. Rep GroupEntryVariant x -> GroupEntryVariant
forall x. GroupEntryVariant -> Rep GroupEntryVariant x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GroupEntryVariant -> Rep GroupEntryVariant x
from :: forall x. GroupEntryVariant -> Rep GroupEntryVariant x
$cto :: forall x. Rep GroupEntryVariant x -> GroupEntryVariant
to :: forall x. Rep GroupEntryVariant x -> GroupEntryVariant
Generic, [GroupEntryVariant] -> Expr
GroupEntryVariant -> Expr
(GroupEntryVariant -> Expr)
-> ([GroupEntryVariant] -> Expr) -> ToExpr GroupEntryVariant
forall a. (a -> Expr) -> ([a] -> Expr) -> ToExpr a
$ctoExpr :: GroupEntryVariant -> Expr
toExpr :: GroupEntryVariant -> Expr
$clistToExpr :: [GroupEntryVariant] -> Expr
listToExpr :: [GroupEntryVariant] -> Expr
ToExpr)
instance HasComment GroupEntry where
commentL :: Lens' GroupEntry Comment
commentL = (GroupEntry -> Comment)
-> (GroupEntry -> Comment -> GroupEntry)
-> Lens' GroupEntry Comment
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens GroupEntry -> Comment
geComment (\GroupEntry
x Comment
y -> GroupEntry
x {geComment = y})
instance CollectComments GroupEntryVariant where
collectComments :: GroupEntryVariant -> [Comment]
collectComments (GEType Maybe MemberKey
_ Type0
t0) = Type0 -> [Comment]
forall a. CollectComments a => a -> [Comment]
collectComments Type0
t0
collectComments (GERef Name
n Maybe GenericArg
mga) = Name -> [Comment]
forall a. CollectComments a => a -> [Comment]
collectComments Name
n [Comment] -> [Comment] -> [Comment]
forall a. Semigroup a => a -> a -> a
<> Maybe GenericArg -> [Comment]
forall a. CollectComments a => a -> [Comment]
collectComments Maybe GenericArg
mga
collectComments (GEGroup Group
g) = Group -> [Comment]
forall a. CollectComments a => a -> [Comment]
collectComments Group
g
data MemberKey
= MKType Type1
| MKBareword Name
| MKValue Value
deriving (MemberKey -> MemberKey -> Bool
(MemberKey -> MemberKey -> Bool)
-> (MemberKey -> MemberKey -> Bool) -> Eq MemberKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MemberKey -> MemberKey -> Bool
== :: MemberKey -> MemberKey -> Bool
$c/= :: MemberKey -> MemberKey -> Bool
/= :: MemberKey -> MemberKey -> Bool
Eq, (forall x. MemberKey -> Rep MemberKey x)
-> (forall x. Rep MemberKey x -> MemberKey) -> Generic MemberKey
forall x. Rep MemberKey x -> MemberKey
forall x. MemberKey -> Rep MemberKey x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. MemberKey -> Rep MemberKey x
from :: forall x. MemberKey -> Rep MemberKey x
$cto :: forall x. Rep MemberKey x -> MemberKey
to :: forall x. Rep MemberKey x -> MemberKey
Generic, Int -> MemberKey -> ShowS
[MemberKey] -> ShowS
MemberKey -> String
(Int -> MemberKey -> ShowS)
-> (MemberKey -> String)
-> ([MemberKey] -> ShowS)
-> Show MemberKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MemberKey -> ShowS
showsPrec :: Int -> MemberKey -> ShowS
$cshow :: MemberKey -> String
show :: MemberKey -> String
$cshowList :: [MemberKey] -> ShowS
showList :: [MemberKey] -> ShowS
Show)
deriving anyclass ([MemberKey] -> Expr
MemberKey -> Expr
(MemberKey -> Expr) -> ([MemberKey] -> Expr) -> ToExpr MemberKey
forall a. (a -> Expr) -> ([a] -> Expr) -> ToExpr a
$ctoExpr :: MemberKey -> Expr
toExpr :: MemberKey -> Expr
$clistToExpr :: [MemberKey] -> Expr
listToExpr :: [MemberKey] -> Expr
ToExpr)
data Value = Value ValueVariant Comment
deriving (Value -> Value -> Bool
(Value -> Value -> Bool) -> (Value -> Value -> Bool) -> Eq Value
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Value -> Value -> Bool
== :: Value -> Value -> Bool
$c/= :: Value -> Value -> Bool
/= :: Value -> Value -> Bool
Eq, (forall x. Value -> Rep Value x)
-> (forall x. Rep Value x -> Value) -> Generic Value
forall x. Rep Value x -> Value
forall x. Value -> Rep Value x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Value -> Rep Value x
from :: forall x. Value -> Rep Value x
$cto :: forall x. Rep Value x -> Value
to :: forall x. Rep Value x -> Value
Generic, Int -> Value -> ShowS
[Value] -> ShowS
Value -> String
(Int -> Value -> ShowS)
-> (Value -> String) -> ([Value] -> ShowS) -> Show Value
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Value -> ShowS
showsPrec :: Int -> Value -> ShowS
$cshow :: Value -> String
show :: Value -> String
$cshowList :: [Value] -> ShowS
showList :: [Value] -> ShowS
Show, Value
Value -> Default Value
forall a. a -> Default a
$cdef :: Value
def :: Value
Default)
deriving anyclass ([Value] -> Expr
Value -> Expr
(Value -> Expr) -> ([Value] -> Expr) -> ToExpr Value
forall a. (a -> Expr) -> ([a] -> Expr) -> ToExpr a
$ctoExpr :: Value -> Expr
toExpr :: Value -> Expr
$clistToExpr :: [Value] -> Expr
listToExpr :: [Value] -> Expr
ToExpr, Eq Value
Eq Value =>
(Int -> Value -> Int) -> (Value -> Int) -> Hashable Value
Int -> Value -> Int
Value -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> Value -> Int
hashWithSalt :: Int -> Value -> Int
$chash :: Value -> Int
hash :: Value -> Int
Hashable, Value -> [Comment]
(Value -> [Comment]) -> CollectComments Value
forall a. (a -> [Comment]) -> CollectComments a
$ccollectComments :: Value -> [Comment]
collectComments :: Value -> [Comment]
CollectComments)
value :: ValueVariant -> Value
value :: ValueVariant -> Value
value ValueVariant
x = ValueVariant -> Comment -> Value
Value ValueVariant
x Comment
forall a. Monoid a => a
mempty
data ValueVariant
= VUInt Word64
| VNInt Word64
| VBignum Integer
| VFloat16 Float
| VFloat32 Float
| VFloat64 Double
| VText T.Text
| VBytes B.ByteString
| VBool Bool
deriving (ValueVariant -> ValueVariant -> Bool
(ValueVariant -> ValueVariant -> Bool)
-> (ValueVariant -> ValueVariant -> Bool) -> Eq ValueVariant
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ValueVariant -> ValueVariant -> Bool
== :: ValueVariant -> ValueVariant -> Bool
$c/= :: ValueVariant -> ValueVariant -> Bool
/= :: ValueVariant -> ValueVariant -> Bool
Eq, (forall x. ValueVariant -> Rep ValueVariant x)
-> (forall x. Rep ValueVariant x -> ValueVariant)
-> Generic ValueVariant
forall x. Rep ValueVariant x -> ValueVariant
forall x. ValueVariant -> Rep ValueVariant x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ValueVariant -> Rep ValueVariant x
from :: forall x. ValueVariant -> Rep ValueVariant x
$cto :: forall x. Rep ValueVariant x -> ValueVariant
to :: forall x. Rep ValueVariant x -> ValueVariant
Generic, Int -> ValueVariant -> ShowS
[ValueVariant] -> ShowS
ValueVariant -> String
(Int -> ValueVariant -> ShowS)
-> (ValueVariant -> String)
-> ([ValueVariant] -> ShowS)
-> Show ValueVariant
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ValueVariant -> ShowS
showsPrec :: Int -> ValueVariant -> ShowS
$cshow :: ValueVariant -> String
show :: ValueVariant -> String
$cshowList :: [ValueVariant] -> ShowS
showList :: [ValueVariant] -> ShowS
Show, ValueVariant
ValueVariant -> Default ValueVariant
forall a. a -> Default a
$cdef :: ValueVariant
def :: ValueVariant
Default)
deriving anyclass ([ValueVariant] -> Expr
ValueVariant -> Expr
(ValueVariant -> Expr)
-> ([ValueVariant] -> Expr) -> ToExpr ValueVariant
forall a. (a -> Expr) -> ([a] -> Expr) -> ToExpr a
$ctoExpr :: ValueVariant -> Expr
toExpr :: ValueVariant -> Expr
$clistToExpr :: [ValueVariant] -> Expr
listToExpr :: [ValueVariant] -> Expr
ToExpr, Eq ValueVariant
Eq ValueVariant =>
(Int -> ValueVariant -> Int)
-> (ValueVariant -> Int) -> Hashable ValueVariant
Int -> ValueVariant -> Int
ValueVariant -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> ValueVariant -> Int
hashWithSalt :: Int -> ValueVariant -> Int
$chash :: ValueVariant -> Int
hash :: ValueVariant -> Int
Hashable, ValueVariant -> [Comment]
(ValueVariant -> [Comment]) -> CollectComments ValueVariant
forall a. (a -> [Comment]) -> CollectComments a
$ccollectComments :: ValueVariant -> [Comment]
collectComments :: ValueVariant -> [Comment]
CollectComments)