Safe Haskell | None |
---|---|
Language | GHC2021 |
Codec.CBOR.Cuddle.CDDL
Description
This module defined the data structure of CDDL as specified in https://datatracker.ietf.org/doc/rfc8610/
Synopsis
- data CDDL = CDDL [Comment] Rule [TopLevel]
- sortCDDL :: CDDL -> CDDL
- cddlTopLevel :: CDDL -> NonEmpty TopLevel
- cddlRules :: CDDL -> NonEmpty Rule
- fromRules :: NonEmpty Rule -> CDDL
- fromRule :: Rule -> CDDL
- data TopLevel
- data Name = Name {
- name :: Text
- nameComment :: Comment
- data Rule = Rule {}
- data TypeOrGroup
- data Assign
- newtype GenericArg = GenericArg (NonEmpty Type1)
- newtype GenericParam = GenericParam (NonEmpty Name)
- newtype Type0 = Type0 {}
- data Type1 = Type1 {}
- data Type2
- data TyOp
- data RangeBound
- data OccurrenceIndicator
- = OIOptional
- | OIZeroOrMore
- | OIOneOrMore
- | OIBounded (Maybe Word64) (Maybe Word64)
- newtype Group = Group {}
- data GroupEntry = GroupEntry {}
- data GroupEntryVariant
- data MemberKey
- data Value = Value ValueVariant Comment
- value :: ValueVariant -> Value
- data ValueVariant
- data GrpChoice = GrpChoice {
- gcGroupEntries :: [GroupEntry]
- gcComment :: Comment
- unwrap :: TypeOrGroup -> Maybe Group
- compareRuleName :: Rule -> Rule -> Ordering
Documentation
The CDDL constructor takes three arguments:
1. Top level comments that precede the first definition
2. The root definition
3. All the other top level comments and definitions
This ensures that CDDL
is correct by construction.
Instances
sortCDDL :: CDDL -> CDDL Source #
Sort the CDDL Rules on the basis of their names Top level comments will be removed!
Constructors
TopLevelRule Rule | |
TopLevelComment Comment |
Instances
Generic TopLevel Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Associated Types
| |||||
Show TopLevel Source # | |||||
Eq TopLevel Source # | |||||
Pretty TopLevel Source # | |||||
Defined in Codec.CBOR.Cuddle.Pretty | |||||
ToExpr TopLevel Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL | |||||
type Rep TopLevel Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL type Rep TopLevel = D1 ('MetaData "TopLevel" "Codec.CBOR.Cuddle.CDDL" "cuddle-0.5.0.0-H0bbRBZdSvH43WSgb38tp7" 'False) (C1 ('MetaCons "TopLevelRule" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rule)) :+: C1 ('MetaCons "TopLevelComment" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Comment))) |
A name can consist of any of the characters from the set {A to
Z, "a" to "z", "0" to "9", "_", "-", "", ".", "$"}, starting
with an alphabetic character (including "
", "_", "$") and ending
in such a character or a digit.
- Names are case sensitive.
- It is preferred style to start a name with a lowercase letter.
- The hyphen is preferred over the underscore (except in a "bareword" (Section 3.5.1), where the semantics may actually require an underscore).
- The period may be useful for larger specifications, to express some module structure (as in "tcp.throughput" vs. "udp.throughput").
- A number of names are predefined in the CDDL prelude, as listed in Appendix D.
- Rule names (types or groups) do not appear in the actual CBOR encoding, but names used as "barewords" in member keys do.
Constructors
Name | |
Fields
|
Instances
IsString Name Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Methods fromString :: String -> Name # | |||||
Generic Name Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Associated Types
| |||||
Show Name Source # | |||||
CollectComments Name Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Methods collectComments :: Name -> [Comment] Source # | |||||
HasComment Name Source # | |||||
Eq Name Source # | |||||
Ord Name Source # | |||||
Hashable Name Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL | |||||
Pretty Name Source # | |||||
Defined in Codec.CBOR.Cuddle.Pretty | |||||
ToExpr Name Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL | |||||
type Rep Name Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL type Rep Name = D1 ('MetaData "Name" "Codec.CBOR.Cuddle.CDDL" "cuddle-0.5.0.0-H0bbRBZdSvH43WSgb38tp7" 'False) (C1 ('MetaCons "Name" 'PrefixI 'True) (S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "nameComment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Comment))) |
rule = typename [genericparm] S assignt S type / groupname [genericparm] S assigng S grpent
typename = id groupname = id
A rule defines a name for a type expression (production "type") or for a group expression (production "grpent"), with the intention that the semantics does not change when the name is replaced by its (parenthesized if needed) definition. Note that whether the name defined by a rule stands for a type or a group isn't always determined by syntax alone: e.g., "a = b" can make "a" a type if "b" is a type, or a group if "b" is a group. More subtly, in "a = (b)", "a" may be used as a type if "b" is a type, or as a group both when "b" is a group and when "b" is a type (a good convention to make the latter case stand out to the human reader is to write "a = (b,)"). (Note that the same dual meaning of parentheses applies within an expression but often can be resolved by the context of the parenthesized expression. On the more general point, it may not be clear immediately either whether "b" stands for a group or a type -- this semantic processing may need to span several levels of rule definitions before a determination can be made.)
Constructors
Rule | |
Fields
|
Instances
Generic Rule Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Associated Types
| |||||
Show Rule Source # | |||||
HasComment Rule Source # | |||||
Eq Rule Source # | |||||
Pretty Rule Source # | |||||
Defined in Codec.CBOR.Cuddle.Pretty | |||||
ToExpr Rule Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL | |||||
type Rep Rule Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL type Rep Rule = D1 ('MetaData "Rule" "Codec.CBOR.Cuddle.CDDL" "cuddle-0.5.0.0-H0bbRBZdSvH43WSgb38tp7" 'False) (C1 ('MetaCons "Rule" 'PrefixI 'True) ((S1 ('MetaSel ('Just "ruleName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Just "ruleGenParam") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe GenericParam))) :*: (S1 ('MetaSel ('Just "ruleAssign") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Assign) :*: (S1 ('MetaSel ('Just "ruleTerm") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TypeOrGroup) :*: S1 ('MetaSel ('Just "ruleComment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Comment))))) |
data TypeOrGroup Source #
Constructors
TOGType Type0 | |
TOGGroup GroupEntry |
Instances
Generic TypeOrGroup Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Associated Types
| |||||
Show TypeOrGroup Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Methods showsPrec :: Int -> TypeOrGroup -> ShowS # show :: TypeOrGroup -> String # showList :: [TypeOrGroup] -> ShowS # | |||||
CollectComments TypeOrGroup Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Methods collectComments :: TypeOrGroup -> [Comment] Source # | |||||
Eq TypeOrGroup Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL | |||||
ToExpr TypeOrGroup Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL | |||||
type Rep TypeOrGroup Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL type Rep TypeOrGroup = D1 ('MetaData "TypeOrGroup" "Codec.CBOR.Cuddle.CDDL" "cuddle-0.5.0.0-H0bbRBZdSvH43WSgb38tp7" 'False) (C1 ('MetaCons "TOGType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type0)) :+: C1 ('MetaCons "TOGGroup" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GroupEntry))) |
assignt = "=" "=" assigng = "=" "/="
A plain equals sign defines the rule name as the equivalent of the expression to the right; it is an error if the name was already defined with a different expression. A "=" or "/=" extends a named type or a group by additional choices; a number of these could be replaced by collecting all the right-hand sides and creating a single rule with a type choice or a group choice built from the right-hand sides in the order of the rules given. (It is not an error to extend a rule name that has not yet been defined; this makes the right-hand side the first entry in the choice being created.)
newtype GenericArg Source #
Constructors
GenericArg (NonEmpty Type1) |
Instances
Semigroup GenericArg Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Methods (<>) :: GenericArg -> GenericArg -> GenericArg # sconcat :: NonEmpty GenericArg -> GenericArg # stimes :: Integral b => b -> GenericArg -> GenericArg # | |||||
Generic GenericArg Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Associated Types
| |||||
Show GenericArg Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Methods showsPrec :: Int -> GenericArg -> ShowS # show :: GenericArg -> String # showList :: [GenericArg] -> ShowS # | |||||
CollectComments GenericArg Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Methods collectComments :: GenericArg -> [Comment] Source # | |||||
Eq GenericArg Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL | |||||
Pretty GenericArg Source # | |||||
Defined in Codec.CBOR.Cuddle.Pretty | |||||
ToExpr GenericArg Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL | |||||
type Rep GenericArg Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL type Rep GenericArg = D1 ('MetaData "GenericArg" "Codec.CBOR.Cuddle.CDDL" "cuddle-0.5.0.0-H0bbRBZdSvH43WSgb38tp7" 'True) (C1 ('MetaCons "GenericArg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty Type1)))) |
newtype GenericParam Source #
Generics
Using angle brackets, the left-hand side of a rule can add formal parameters after the name being defined, as in:
messages = message"now" / message1..100 messagev = {type: t, value: v}
When using a generic rule, the formal parameters are bound to the actual arguments supplied (also using angle brackets), within the scope of the generic rule (as if there were a rule of the form parameter = argument).
Generic rules can be used for establishing names for both types and groups.
Constructors
GenericParam (NonEmpty Name) |
Instances
Semigroup GenericParam Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Methods (<>) :: GenericParam -> GenericParam -> GenericParam # sconcat :: NonEmpty GenericParam -> GenericParam # stimes :: Integral b => b -> GenericParam -> GenericParam # | |||||
Generic GenericParam Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Associated Types
| |||||
Show GenericParam Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Methods showsPrec :: Int -> GenericParam -> ShowS # show :: GenericParam -> String # showList :: [GenericParam] -> ShowS # | |||||
Eq GenericParam Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL | |||||
Pretty GenericParam Source # | |||||
Defined in Codec.CBOR.Cuddle.Pretty | |||||
ToExpr GenericParam Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL | |||||
type Rep GenericParam Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL type Rep GenericParam = D1 ('MetaData "GenericParam" "Codec.CBOR.Cuddle.CDDL" "cuddle-0.5.0.0-H0bbRBZdSvH43WSgb38tp7" 'True) (C1 ('MetaCons "GenericParam" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty Name)))) |
A type can be given as a choice between one or more types. The choice matches a data item if the data item matches any one of the types given in the choice.
Instances
Semigroup Type0 Source # | |||||
Generic Type0 Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Associated Types
| |||||
Show Type0 Source # | |||||
CollectComments Type0 Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Methods collectComments :: Type0 -> [Comment] Source # | |||||
HasComment Type0 Source # | |||||
Eq Type0 Source # | |||||
Pretty Type0 Source # | |||||
Defined in Codec.CBOR.Cuddle.Pretty | |||||
ToExpr Type0 Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL | |||||
type Rep Type0 Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL |
Two types can be combined with a range operator (see below)
Instances
Generic Type1 Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Associated Types
| |||||
Show Type1 Source # | |||||
CollectComments Type1 Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Methods collectComments :: Type1 -> [Comment] Source # | |||||
HasComment Type1 Source # | |||||
Default Type1 Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL | |||||
Eq Type1 Source # | |||||
Pretty Type1 Source # | |||||
Defined in Codec.CBOR.Cuddle.Pretty | |||||
ToExpr Type1 Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL | |||||
type Rep Type1 Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL type Rep Type1 = D1 ('MetaData "Type1" "Codec.CBOR.Cuddle.CDDL" "cuddle-0.5.0.0-H0bbRBZdSvH43WSgb38tp7" 'False) (C1 ('MetaCons "Type1" 'PrefixI 'True) (S1 ('MetaSel ('Just "t1Main") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type2) :*: (S1 ('MetaSel ('Just "t1TyOp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (TyOp, Type2))) :*: S1 ('MetaSel ('Just "t1Comment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Comment)))) |
Constructors
T2Value Value | A type can be just a single value (such as 1 or "icecream" or h'0815'), which matches only a data item with that specific value (no conversions defined), |
T2Name Name (Maybe GenericArg) | or be defined by a rule giving a meaning to a name (possibly after supplying generic arguments as required by the generic parameters) |
T2Group Type0 | or be defined in a parenthesized type expression (parentheses may be necessary to override some operator precedence), |
T2Map Group | a map expression, which matches a valid CBOR map the key/value pairs of which can be ordered in such a way that the resulting sequence matches the group expression, or |
T2Array Group | an array expression, which matches a CBOR array the elements of which when taken as values and complemented by a wildcard (matches anything) key each -- match the group, or |
T2Unwrapped Name (Maybe GenericArg) | an "unwrapped" group (see Section 3.7), which matches the group inside a type defined as a map or an array by wrapping the group, or |
T2Enum Group | an enumeration expression, which matches any value that is within the set of values that the values of the group given can take, or |
T2EnumRef Name (Maybe GenericArg) | |
T2Tag (Maybe Word64) Type0 | a tagged data item, tagged with the "uint" given and containing the type given as the tagged value, or |
T2DataItem Word8 (Maybe Word64) | a data item of a major type (given by the DIGIT), optionally constrained to the additional information given by the uint, or |
T2Any | Any data item |
Instances
Generic Type2 Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Associated Types
| |||||
Show Type2 Source # | |||||
CollectComments Type2 Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Methods collectComments :: Type2 -> [Comment] Source # | |||||
Default Type2 Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL | |||||
Eq Type2 Source # | |||||
Pretty Type2 Source # | |||||
Defined in Codec.CBOR.Cuddle.Pretty | |||||
ToExpr Type2 Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL | |||||
type Rep Type2 Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL type Rep Type2 = D1 ('MetaData "Type2" "Codec.CBOR.Cuddle.CDDL" "cuddle-0.5.0.0-H0bbRBZdSvH43WSgb38tp7" 'False) (((C1 ('MetaCons "T2Value" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Value)) :+: C1 ('MetaCons "T2Name" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe GenericArg)))) :+: (C1 ('MetaCons "T2Group" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type0)) :+: (C1 ('MetaCons "T2Map" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Group)) :+: C1 ('MetaCons "T2Array" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Group))))) :+: ((C1 ('MetaCons "T2Unwrapped" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe GenericArg))) :+: (C1 ('MetaCons "T2Enum" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Group)) :+: C1 ('MetaCons "T2EnumRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe GenericArg))))) :+: (C1 ('MetaCons "T2Tag" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Word64)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type0)) :+: (C1 ('MetaCons "T2DataItem" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word8) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Word64))) :+: C1 ('MetaCons "T2Any" 'PrefixI 'False) (U1 :: Type -> Type))))) |
Constructors
RangeOp RangeBound | |
CtrlOp CtlOp |
Instances
Generic TyOp Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Associated Types
| |||||
Show TyOp Source # | |||||
Eq TyOp Source # | |||||
Pretty TyOp Source # | |||||
Defined in Codec.CBOR.Cuddle.Pretty | |||||
ToExpr TyOp Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL | |||||
type Rep TyOp Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL type Rep TyOp = D1 ('MetaData "TyOp" "Codec.CBOR.Cuddle.CDDL" "cuddle-0.5.0.0-H0bbRBZdSvH43WSgb38tp7" 'False) (C1 ('MetaCons "RangeOp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RangeBound)) :+: C1 ('MetaCons "CtrlOp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CtlOp))) |
data RangeBound Source #
A range operator can be used to join two type expressions that stand for either two integer values or two floating-point values; it matches any value that is between the two values, where the first value is always included in the matching set and the second value is included for ".." and excluded for "...".
Instances
Generic RangeBound Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Associated Types
| |||||
Show RangeBound Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Methods showsPrec :: Int -> RangeBound -> ShowS # show :: RangeBound -> String # showList :: [RangeBound] -> ShowS # | |||||
Eq RangeBound Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL | |||||
Hashable RangeBound Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL | |||||
ToExpr RangeBound Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL | |||||
type Rep RangeBound Source # | |||||
data OccurrenceIndicator Source #
An optional _occurrence_ indicator can be given in front of a group entry. It is either (1) one of the characters "?" (optional), "*" (zero or more), or "+" (one or more) or (2) of the form n*m, where n and m are optional unsigned integers and n is the lower limit (default 0) and m is the upper limit (default no limit) of occurrences.
If no occurrence indicator is specified, the group entry is to occur exactly once (as if 1*1 were specified). A group entry with an occurrence indicator matches sequences of name/value pairs that are composed by concatenating a number of sequences that the basic group entry matches, where the number needs to be allowed by the occurrence indicator.
Constructors
OIOptional | |
OIZeroOrMore | |
OIOneOrMore | |
OIBounded (Maybe Word64) (Maybe Word64) |
Instances
Generic OccurrenceIndicator Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Associated Types
Methods from :: OccurrenceIndicator -> Rep OccurrenceIndicator x # to :: Rep OccurrenceIndicator x -> OccurrenceIndicator # | |||||
Show OccurrenceIndicator Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Methods showsPrec :: Int -> OccurrenceIndicator -> ShowS # show :: OccurrenceIndicator -> String # showList :: [OccurrenceIndicator] -> ShowS # | |||||
Eq OccurrenceIndicator Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Methods (==) :: OccurrenceIndicator -> OccurrenceIndicator -> Bool # (/=) :: OccurrenceIndicator -> OccurrenceIndicator -> Bool # | |||||
Hashable OccurrenceIndicator Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL | |||||
Pretty OccurrenceIndicator Source # | |||||
Defined in Codec.CBOR.Cuddle.Pretty | |||||
ToExpr OccurrenceIndicator Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL | |||||
type Rep OccurrenceIndicator Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL type Rep OccurrenceIndicator = D1 ('MetaData "OccurrenceIndicator" "Codec.CBOR.Cuddle.CDDL" "cuddle-0.5.0.0-H0bbRBZdSvH43WSgb38tp7" 'False) ((C1 ('MetaCons "OIOptional" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OIZeroOrMore" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OIOneOrMore" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OIBounded" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Word64)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Word64))))) |
A group matches any sequence of key/value pairs that matches any of the choices given (again using PEG semantics).
Instances
Semigroup Group Source # | |||||
Generic Group Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Associated Types
| |||||
Show Group Source # | |||||
CollectComments Group Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Methods collectComments :: Group -> [Comment] Source # | |||||
HasComment Group Source # | |||||
Eq Group Source # | |||||
ToExpr Group Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL | |||||
type Rep Group Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL |
data GroupEntry Source #
A group entry can be given by a value type, which needs to be matched by the value part of a single element; and, optionally, a memberkey type, which needs to be matched by the key part of the element, if the memberkey is given. If the memberkey is not given, the entry can only be used for matching arrays, not for maps. (See below for how that is modified by the occurrence indicator.)
Constructors
GroupEntry | |
Instances
Generic GroupEntry Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Associated Types
| |||||
Show GroupEntry Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Methods showsPrec :: Int -> GroupEntry -> ShowS # show :: GroupEntry -> String # showList :: [GroupEntry] -> ShowS # | |||||
CollectComments GroupEntry Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Methods collectComments :: GroupEntry -> [Comment] Source # | |||||
HasComment GroupEntry Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL | |||||
Eq GroupEntry Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL | |||||
Pretty GroupEntry Source # | |||||
Defined in Codec.CBOR.Cuddle.Pretty | |||||
ToExpr GroupEntry Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL | |||||
type Rep GroupEntry Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL type Rep GroupEntry = D1 ('MetaData "GroupEntry" "Codec.CBOR.Cuddle.CDDL" "cuddle-0.5.0.0-H0bbRBZdSvH43WSgb38tp7" 'False) (C1 ('MetaCons "GroupEntry" 'PrefixI 'True) (S1 ('MetaSel ('Just "geOccurrenceIndicator") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe OccurrenceIndicator)) :*: (S1 ('MetaSel ('Just "geComment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Comment) :*: S1 ('MetaSel ('Just "geVariant") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GroupEntryVariant)))) |
data GroupEntryVariant Source #
Instances
Generic GroupEntryVariant Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Associated Types
Methods from :: GroupEntryVariant -> Rep GroupEntryVariant x # to :: Rep GroupEntryVariant x -> GroupEntryVariant # | |||||
Show GroupEntryVariant Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Methods showsPrec :: Int -> GroupEntryVariant -> ShowS # show :: GroupEntryVariant -> String # showList :: [GroupEntryVariant] -> ShowS # | |||||
CollectComments GroupEntryVariant Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Methods collectComments :: GroupEntryVariant -> [Comment] Source # | |||||
Eq GroupEntryVariant Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Methods (==) :: GroupEntryVariant -> GroupEntryVariant -> Bool # (/=) :: GroupEntryVariant -> GroupEntryVariant -> Bool # | |||||
ToExpr GroupEntryVariant Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL | |||||
type Rep GroupEntryVariant Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL type Rep GroupEntryVariant = D1 ('MetaData "GroupEntryVariant" "Codec.CBOR.Cuddle.CDDL" "cuddle-0.5.0.0-H0bbRBZdSvH43WSgb38tp7" 'False) (C1 ('MetaCons "GEType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe MemberKey)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type0)) :+: (C1 ('MetaCons "GERef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe GenericArg))) :+: C1 ('MetaCons "GEGroup" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Group)))) |
Key types can be given by a type expression, a bareword (which stands for a type that just contains a string value created from this bareword), or a value (which stands for a type that just contains this value). A key value matches its key type if the key value is a member of the key type, unless a cut preceding it in the group applies (see Section 3.5.4 for how map matching is influenced by the presence of the cuts denoted by "^" or ":" in previous entries).
Instances
Generic MemberKey Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Associated Types
| |||||
Show MemberKey Source # | |||||
Eq MemberKey Source # | |||||
Pretty MemberKey Source # | |||||
Defined in Codec.CBOR.Cuddle.Pretty | |||||
ToExpr MemberKey Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL | |||||
type Rep MemberKey Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL type Rep MemberKey = D1 ('MetaData "MemberKey" "Codec.CBOR.Cuddle.CDDL" "cuddle-0.5.0.0-H0bbRBZdSvH43WSgb38tp7" 'False) (C1 ('MetaCons "MKType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type1)) :+: (C1 ('MetaCons "MKBareword" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)) :+: C1 ('MetaCons "MKValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Value)))) |
Constructors
Value ValueVariant Comment |
Instances
Generic Value Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Associated Types
| |||||
Show Value Source # | |||||
CollectComments Value Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Methods collectComments :: Value -> [Comment] Source # | |||||
Default Value Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL | |||||
Eq Value Source # | |||||
Hashable Value Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL | |||||
Pretty Value Source # | |||||
Defined in Codec.CBOR.Cuddle.Pretty | |||||
ToExpr Value Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL | |||||
type Rep Value Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL type Rep Value = D1 ('MetaData "Value" "Codec.CBOR.Cuddle.CDDL" "cuddle-0.5.0.0-H0bbRBZdSvH43WSgb38tp7" 'False) (C1 ('MetaCons "Value" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ValueVariant) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Comment))) |
value :: ValueVariant -> Value Source #
data ValueVariant Source #
Constructors
VUInt Word64 | |
VNInt Word64 | |
VBignum Integer | |
VFloat16 Float | |
VFloat32 Float | |
VFloat64 Double | |
VText Text | |
VBytes ByteString | |
VBool Bool |
Instances
Generic ValueVariant Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Associated Types
| |||||
Show ValueVariant Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Methods showsPrec :: Int -> ValueVariant -> ShowS # show :: ValueVariant -> String # showList :: [ValueVariant] -> ShowS # | |||||
CollectComments ValueVariant Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Methods collectComments :: ValueVariant -> [Comment] Source # | |||||
Default ValueVariant Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Methods def :: ValueVariant # | |||||
Eq ValueVariant Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL | |||||
Hashable ValueVariant Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL | |||||
Pretty ValueVariant Source # | |||||
Defined in Codec.CBOR.Cuddle.Pretty | |||||
ToExpr ValueVariant Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL | |||||
type Rep ValueVariant Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL type Rep ValueVariant = D1 ('MetaData "ValueVariant" "Codec.CBOR.Cuddle.CDDL" "cuddle-0.5.0.0-H0bbRBZdSvH43WSgb38tp7" 'False) (((C1 ('MetaCons "VUInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)) :+: C1 ('MetaCons "VNInt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64))) :+: (C1 ('MetaCons "VBignum" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)) :+: C1 ('MetaCons "VFloat16" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float)))) :+: ((C1 ('MetaCons "VFloat32" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float)) :+: C1 ('MetaCons "VFloat64" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double))) :+: (C1 ('MetaCons "VText" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: (C1 ('MetaCons "VBytes" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)) :+: C1 ('MetaCons "VBool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))))) |
Constructors
GrpChoice | |
Fields
|
Instances
Generic GrpChoice Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Associated Types
| |||||
Show GrpChoice Source # | |||||
CollectComments GrpChoice Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL Methods collectComments :: GrpChoice -> [Comment] Source # | |||||
HasComment GrpChoice Source # | |||||
Eq GrpChoice Source # | |||||
ToExpr GrpChoice Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL | |||||
type Rep GrpChoice Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL type Rep GrpChoice = D1 ('MetaData "GrpChoice" "Codec.CBOR.Cuddle.CDDL" "cuddle-0.5.0.0-H0bbRBZdSvH43WSgb38tp7" 'False) (C1 ('MetaCons "GrpChoice" 'PrefixI 'True) (S1 ('MetaSel ('Just "gcGroupEntries") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [GroupEntry]) :*: S1 ('MetaSel ('Just "gcComment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Comment))) |