Safe Haskell | None |
---|---|
Language | GHC2021 |
Codec.CBOR.Cuddle.CDDL.CTree
Contents
Synopsis
- data CTree (f :: Type -> Type)
- traverseCTree :: Monad m => (Node f -> m (Node g)) -> CTree f -> m (CTree g)
- type Node (f :: Type -> Type) = f (CTree f)
- newtype CTreeRoot' (poly :: Type -> Type) (f :: Type -> Type) = CTreeRoot (Map Name (poly (Node f)))
- type CTreeRoot (f :: Type -> Type) = CTreeRoot' (ParametrisedWith [Name]) f
- data ParametrisedWith w a
- = Unparametrised {
- underlying :: a
- | Parametrised {
- underlying :: a
- params :: w
- = Unparametrised {
Resolved CDDL Tree
data CTree (f :: Type -> Type) Source #
CDDL Tree, parametrised over a functor
We principally use this functor to represent references - thus, every 'f a' may be either an a or a reference to another CTree.
Constructors
Literal Value | |
Postlude PTerm | |
Map [Node f] | |
Array [Node f] | |
Choice (NonEmpty (Node f)) | |
Group [Node f] | |
KV | |
Occur | |
Fields
| |
Range | |
Control | |
Enum (Node f) | |
Unwrap (Node f) | |
Tag Word64 (Node f) |
Instances
traverseCTree :: Monad m => (Node f -> m (Node g)) -> CTree f -> m (CTree g) Source #
Traverse the CTree, carrying out the given operation at each node
newtype CTreeRoot' (poly :: Type -> Type) (f :: Type -> Type) Source #
Instances
Generic (CTreeRoot' poly f) Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL.CTree Associated Types
Methods from :: CTreeRoot' poly f -> Rep (CTreeRoot' poly f) x # to :: Rep (CTreeRoot' poly f) x -> CTreeRoot' poly f # | |||||
Show (poly (Node MonoRef)) => Show (CTreeRoot' poly MonoRef) Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL.Resolve | |||||
type Rep (CTreeRoot' poly f) Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL.CTree type Rep (CTreeRoot' poly f) = D1 ('MetaData "CTreeRoot'" "Codec.CBOR.Cuddle.CDDL.CTree" "cuddle-0.5.0.0-H0bbRBZdSvH43WSgb38tp7" 'True) (C1 ('MetaCons "CTreeRoot" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Name (poly (Node f)))))) |
type CTreeRoot (f :: Type -> Type) = CTreeRoot' (ParametrisedWith [Name]) f Source #
data ParametrisedWith w a Source #
Constructors
Unparametrised | |
Fields
| |
Parametrised | |
Fields
|
Instances
Foldable (ParametrisedWith w) Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL.CTree Methods fold :: Monoid m => ParametrisedWith w m -> m # foldMap :: Monoid m => (a -> m) -> ParametrisedWith w a -> m # foldMap' :: Monoid m => (a -> m) -> ParametrisedWith w a -> m # foldr :: (a -> b -> b) -> b -> ParametrisedWith w a -> b # foldr' :: (a -> b -> b) -> b -> ParametrisedWith w a -> b # foldl :: (b -> a -> b) -> b -> ParametrisedWith w a -> b # foldl' :: (b -> a -> b) -> b -> ParametrisedWith w a -> b # foldr1 :: (a -> a -> a) -> ParametrisedWith w a -> a # foldl1 :: (a -> a -> a) -> ParametrisedWith w a -> a # toList :: ParametrisedWith w a -> [a] # null :: ParametrisedWith w a -> Bool # length :: ParametrisedWith w a -> Int # elem :: Eq a => a -> ParametrisedWith w a -> Bool # maximum :: Ord a => ParametrisedWith w a -> a # minimum :: Ord a => ParametrisedWith w a -> a # sum :: Num a => ParametrisedWith w a -> a # product :: Num a => ParametrisedWith w a -> a # | |||||
Traversable (ParametrisedWith w) Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL.CTree Methods traverse :: Applicative f => (a -> f b) -> ParametrisedWith w a -> f (ParametrisedWith w b) # sequenceA :: Applicative f => ParametrisedWith w (f a) -> f (ParametrisedWith w a) # mapM :: Monad m => (a -> m b) -> ParametrisedWith w a -> m (ParametrisedWith w b) # sequence :: Monad m => ParametrisedWith w (m a) -> m (ParametrisedWith w a) # | |||||
Functor (ParametrisedWith w) Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL.CTree Methods fmap :: (a -> b) -> ParametrisedWith w a -> ParametrisedWith w b # (<$) :: a -> ParametrisedWith w b -> ParametrisedWith w a # | |||||
Generic (ParametrisedWith w a) Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL.CTree Associated Types
Methods from :: ParametrisedWith w a -> Rep (ParametrisedWith w a) x # to :: Rep (ParametrisedWith w a) x -> ParametrisedWith w a # | |||||
(Show a, Show w) => Show (ParametrisedWith w a) Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL.CTree Methods showsPrec :: Int -> ParametrisedWith w a -> ShowS # show :: ParametrisedWith w a -> String # showList :: [ParametrisedWith w a] -> ShowS # | |||||
(Eq a, Eq w) => Eq (ParametrisedWith w a) Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL.CTree Methods (==) :: ParametrisedWith w a -> ParametrisedWith w a -> Bool # (/=) :: ParametrisedWith w a -> ParametrisedWith w a -> Bool # | |||||
(Hashable w, Hashable a) => Hashable (ParametrisedWith w a) Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL.CTree | |||||
type Rep (ParametrisedWith w a) Source # | |||||
Defined in Codec.CBOR.Cuddle.CDDL.CTree type Rep (ParametrisedWith w a) = D1 ('MetaData "ParametrisedWith" "Codec.CBOR.Cuddle.CDDL.CTree" "cuddle-0.5.0.0-H0bbRBZdSvH43WSgb38tp7" 'False) (C1 ('MetaCons "Unparametrised" 'PrefixI 'True) (S1 ('MetaSel ('Just "underlying") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "Parametrised" 'PrefixI 'True) (S1 ('MetaSel ('Just "underlying") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "params") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 w))) |