{-# LANGUAGE DataKinds #-}
module Codec.CBOR.Cuddle.CDDL.CTree where
import Codec.CBOR.Cuddle.CDDL (
Name,
OccurrenceIndicator,
RangeBound,
Value,
)
import Codec.CBOR.Cuddle.CDDL.CtlOp
import Codec.CBOR.Cuddle.CDDL.Postlude (PTerm)
import Data.Hashable (Hashable)
import Data.List.NonEmpty qualified as NE
import Data.Map.Strict qualified as Map
import Data.Word (Word64)
import GHC.Generics (Generic)
data CTree f
= Literal Value
| Postlude PTerm
| Map [Node f]
| Array [Node f]
| Choice (NE.NonEmpty (Node f))
| Group [Node f]
| KV {forall (f :: * -> *). CTree f -> Node f
key :: Node f, forall (f :: * -> *). CTree f -> Node f
value :: Node f, forall (f :: * -> *). CTree f -> Bool
cut :: Bool}
| Occur {forall (f :: * -> *). CTree f -> Node f
item :: Node f, forall (f :: * -> *). CTree f -> OccurrenceIndicator
occurs :: OccurrenceIndicator}
| Range {forall (f :: * -> *). CTree f -> Node f
from :: Node f, forall (f :: * -> *). CTree f -> Node f
to :: Node f, forall (f :: * -> *). CTree f -> RangeBound
inclusive :: RangeBound}
| Control {forall (f :: * -> *). CTree f -> CtlOp
op :: CtlOp, forall (f :: * -> *). CTree f -> Node f
target :: Node f, forall (f :: * -> *). CTree f -> Node f
controller :: Node f}
| Enum (Node f)
| Unwrap (Node f)
| Tag Word64 (Node f)
deriving ((forall x. CTree f -> Rep (CTree f) x)
-> (forall x. Rep (CTree f) x -> CTree f) -> Generic (CTree f)
forall x. Rep (CTree f) x -> CTree f
forall x. CTree f -> Rep (CTree f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (f :: * -> *) x. Rep (CTree f) x -> CTree f
forall (f :: * -> *) x. CTree f -> Rep (CTree f) x
$cfrom :: forall (f :: * -> *) x. CTree f -> Rep (CTree f) x
from :: forall x. CTree f -> Rep (CTree f) x
$cto :: forall (f :: * -> *) x. Rep (CTree f) x -> CTree f
to :: forall x. Rep (CTree f) x -> CTree f
Generic)
traverseCTree :: Monad m => (Node f -> m (Node g)) -> CTree f -> m (CTree g)
traverseCTree :: forall (m :: * -> *) (f :: * -> *) (g :: * -> *).
Monad m =>
(Node f -> m (Node g)) -> CTree f -> m (CTree g)
traverseCTree Node f -> m (Node g)
_ (Literal Value
a) = CTree g -> m (CTree g)
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (CTree g -> m (CTree g)) -> CTree g -> m (CTree g)
forall a b. (a -> b) -> a -> b
$ Value -> CTree g
forall (f :: * -> *). Value -> CTree f
Literal Value
a
traverseCTree Node f -> m (Node g)
_ (Postlude PTerm
a) = CTree g -> m (CTree g)
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (CTree g -> m (CTree g)) -> CTree g -> m (CTree g)
forall a b. (a -> b) -> a -> b
$ PTerm -> CTree g
forall (f :: * -> *). PTerm -> CTree f
Postlude PTerm
a
traverseCTree Node f -> m (Node g)
atNode (Map [Node f]
xs) = [Node g] -> CTree g
forall (f :: * -> *). [Node f] -> CTree f
Map ([Node g] -> CTree g) -> m [Node g] -> m (CTree g)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Node f -> m (Node g)) -> [Node f] -> m [Node g]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse Node f -> m (Node g)
atNode [Node f]
xs
traverseCTree Node f -> m (Node g)
atNode (Array [Node f]
xs) = [Node g] -> CTree g
forall (f :: * -> *). [Node f] -> CTree f
Array ([Node g] -> CTree g) -> m [Node g] -> m (CTree g)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Node f -> m (Node g)) -> [Node f] -> m [Node g]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse Node f -> m (Node g)
atNode [Node f]
xs
traverseCTree Node f -> m (Node g)
atNode (Group [Node f]
xs) = [Node g] -> CTree g
forall (f :: * -> *). [Node f] -> CTree f
Group ([Node g] -> CTree g) -> m [Node g] -> m (CTree g)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Node f -> m (Node g)) -> [Node f] -> m [Node g]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse Node f -> m (Node g)
atNode [Node f]
xs
traverseCTree Node f -> m (Node g)
atNode (Choice NonEmpty (Node f)
xs) = NonEmpty (Node g) -> CTree g
forall (f :: * -> *). NonEmpty (Node f) -> CTree f
Choice (NonEmpty (Node g) -> CTree g)
-> m (NonEmpty (Node g)) -> m (CTree g)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Node f -> m (Node g))
-> NonEmpty (Node f) -> m (NonEmpty (Node g))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> NonEmpty a -> f (NonEmpty b)
traverse Node f -> m (Node g)
atNode NonEmpty (Node f)
xs
traverseCTree Node f -> m (Node g)
atNode (KV Node f
k Node f
v Bool
c) = do
Node g
k' <- Node f -> m (Node g)
atNode Node f
k
Node g
v' <- Node f -> m (Node g)
atNode Node f
v
CTree g -> m (CTree g)
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (CTree g -> m (CTree g)) -> CTree g -> m (CTree g)
forall a b. (a -> b) -> a -> b
$ Node g -> Node g -> Bool -> CTree g
forall (f :: * -> *). Node f -> Node f -> Bool -> CTree f
KV Node g
k' Node g
v' Bool
c
traverseCTree Node f -> m (Node g)
atNode (Occur Node f
i OccurrenceIndicator
occ) = (Node g -> OccurrenceIndicator -> CTree g)
-> OccurrenceIndicator -> Node g -> CTree g
forall a b c. (a -> b -> c) -> b -> a -> c
flip Node g -> OccurrenceIndicator -> CTree g
forall (f :: * -> *). Node f -> OccurrenceIndicator -> CTree f
Occur OccurrenceIndicator
occ (Node g -> CTree g) -> m (Node g) -> m (CTree g)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Node f -> m (Node g)
atNode Node f
i
traverseCTree Node f -> m (Node g)
atNode (Range Node f
f Node f
t RangeBound
inc) = do
Node g
f' <- Node f -> m (Node g)
atNode Node f
f
Node g
t' <- Node f -> m (Node g)
atNode Node f
t
CTree g -> m (CTree g)
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (CTree g -> m (CTree g)) -> CTree g -> m (CTree g)
forall a b. (a -> b) -> a -> b
$ Node g -> Node g -> RangeBound -> CTree g
forall (f :: * -> *). Node f -> Node f -> RangeBound -> CTree f
Range Node g
f' Node g
t' RangeBound
inc
traverseCTree Node f -> m (Node g)
atNode (Control CtlOp
o Node f
t Node f
c) = do
Node g
t' <- Node f -> m (Node g)
atNode Node f
t
Node g
c' <- Node f -> m (Node g)
atNode Node f
c
CTree g -> m (CTree g)
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (CTree g -> m (CTree g)) -> CTree g -> m (CTree g)
forall a b. (a -> b) -> a -> b
$ CtlOp -> Node g -> Node g -> CTree g
forall (f :: * -> *). CtlOp -> Node f -> Node f -> CTree f
Control CtlOp
o Node g
t' Node g
c'
traverseCTree Node f -> m (Node g)
atNode (Enum Node f
ref) = Node g -> CTree g
forall (f :: * -> *). Node f -> CTree f
Enum (Node g -> CTree g) -> m (Node g) -> m (CTree g)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Node f -> m (Node g)
atNode Node f
ref
traverseCTree Node f -> m (Node g)
atNode (Unwrap Node f
ref) = Node g -> CTree g
forall (f :: * -> *). Node f -> CTree f
Unwrap (Node g -> CTree g) -> m (Node g) -> m (CTree g)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Node f -> m (Node g)
atNode Node f
ref
traverseCTree Node f -> m (Node g)
atNode (Tag Word64
i Node f
ref) = Word64 -> Node g -> CTree g
forall (f :: * -> *). Word64 -> Node f -> CTree f
Tag Word64
i (Node g -> CTree g) -> m (Node g) -> m (CTree g)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Node f -> m (Node g)
atNode Node f
ref
type Node f = f (CTree f)
newtype CTreeRoot' poly f
= CTreeRoot
(Map.Map Name (poly (Node f)))
deriving ((forall x. CTreeRoot' poly f -> Rep (CTreeRoot' poly f) x)
-> (forall x. Rep (CTreeRoot' poly f) x -> CTreeRoot' poly f)
-> Generic (CTreeRoot' poly f)
forall x. Rep (CTreeRoot' poly f) x -> CTreeRoot' poly f
forall x. CTreeRoot' poly f -> Rep (CTreeRoot' poly f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (poly :: * -> *) (f :: * -> *) x.
Rep (CTreeRoot' poly f) x -> CTreeRoot' poly f
forall (poly :: * -> *) (f :: * -> *) x.
CTreeRoot' poly f -> Rep (CTreeRoot' poly f) x
$cfrom :: forall (poly :: * -> *) (f :: * -> *) x.
CTreeRoot' poly f -> Rep (CTreeRoot' poly f) x
from :: forall x. CTreeRoot' poly f -> Rep (CTreeRoot' poly f) x
$cto :: forall (poly :: * -> *) (f :: * -> *) x.
Rep (CTreeRoot' poly f) x -> CTreeRoot' poly f
to :: forall x. Rep (CTreeRoot' poly f) x -> CTreeRoot' poly f
Generic)
type CTreeRoot f = CTreeRoot' (ParametrisedWith [Name]) f
data ParametrisedWith w a
= Unparametrised {forall w a. ParametrisedWith w a -> a
underlying :: a}
| Parametrised
{ underlying :: a
, forall w a. ParametrisedWith w a -> w
params :: w
}
deriving (ParametrisedWith w a -> ParametrisedWith w a -> Bool
(ParametrisedWith w a -> ParametrisedWith w a -> Bool)
-> (ParametrisedWith w a -> ParametrisedWith w a -> Bool)
-> Eq (ParametrisedWith w a)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall w a.
(Eq a, Eq w) =>
ParametrisedWith w a -> ParametrisedWith w a -> Bool
$c== :: forall w a.
(Eq a, Eq w) =>
ParametrisedWith w a -> ParametrisedWith w a -> Bool
== :: ParametrisedWith w a -> ParametrisedWith w a -> Bool
$c/= :: forall w a.
(Eq a, Eq w) =>
ParametrisedWith w a -> ParametrisedWith w a -> Bool
/= :: ParametrisedWith w a -> ParametrisedWith w a -> Bool
Eq, (forall a b.
(a -> b) -> ParametrisedWith w a -> ParametrisedWith w b)
-> (forall a b. a -> ParametrisedWith w b -> ParametrisedWith w a)
-> Functor (ParametrisedWith w)
forall a b. a -> ParametrisedWith w b -> ParametrisedWith w a
forall a b.
(a -> b) -> ParametrisedWith w a -> ParametrisedWith w b
forall w a b. a -> ParametrisedWith w b -> ParametrisedWith w a
forall w a b.
(a -> b) -> ParametrisedWith w a -> ParametrisedWith w b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall w a b.
(a -> b) -> ParametrisedWith w a -> ParametrisedWith w b
fmap :: forall a b.
(a -> b) -> ParametrisedWith w a -> ParametrisedWith w b
$c<$ :: forall w a b. a -> ParametrisedWith w b -> ParametrisedWith w a
<$ :: forall a b. a -> ParametrisedWith w b -> ParametrisedWith w a
Functor, (forall x. ParametrisedWith w a -> Rep (ParametrisedWith w a) x)
-> (forall x. Rep (ParametrisedWith w a) x -> ParametrisedWith w a)
-> Generic (ParametrisedWith w a)
forall x. Rep (ParametrisedWith w a) x -> ParametrisedWith w a
forall x. ParametrisedWith w a -> Rep (ParametrisedWith w a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall w a x. Rep (ParametrisedWith w a) x -> ParametrisedWith w a
forall w a x. ParametrisedWith w a -> Rep (ParametrisedWith w a) x
$cfrom :: forall w a x. ParametrisedWith w a -> Rep (ParametrisedWith w a) x
from :: forall x. ParametrisedWith w a -> Rep (ParametrisedWith w a) x
$cto :: forall w a x. Rep (ParametrisedWith w a) x -> ParametrisedWith w a
to :: forall x. Rep (ParametrisedWith w a) x -> ParametrisedWith w a
Generic, (forall m. Monoid m => ParametrisedWith w m -> m)
-> (forall m a. Monoid m => (a -> m) -> ParametrisedWith w a -> m)
-> (forall m a. Monoid m => (a -> m) -> ParametrisedWith w a -> m)
-> (forall a b. (a -> b -> b) -> b -> ParametrisedWith w a -> b)
-> (forall a b. (a -> b -> b) -> b -> ParametrisedWith w a -> b)
-> (forall b a. (b -> a -> b) -> b -> ParametrisedWith w a -> b)
-> (forall b a. (b -> a -> b) -> b -> ParametrisedWith w a -> b)
-> (forall a. (a -> a -> a) -> ParametrisedWith w a -> a)
-> (forall a. (a -> a -> a) -> ParametrisedWith w a -> a)
-> (forall a. ParametrisedWith w a -> [a])
-> (forall a. ParametrisedWith w a -> Bool)
-> (forall a. ParametrisedWith w a -> Int)
-> (forall a. Eq a => a -> ParametrisedWith w a -> Bool)
-> (forall a. Ord a => ParametrisedWith w a -> a)
-> (forall a. Ord a => ParametrisedWith w a -> a)
-> (forall a. Num a => ParametrisedWith w a -> a)
-> (forall a. Num a => ParametrisedWith w a -> a)
-> Foldable (ParametrisedWith w)
forall a. Eq a => a -> ParametrisedWith w a -> Bool
forall a. Num a => ParametrisedWith w a -> a
forall a. Ord a => ParametrisedWith w a -> a
forall m. Monoid m => ParametrisedWith w m -> m
forall a. ParametrisedWith w a -> Bool
forall a. ParametrisedWith w a -> Int
forall a. ParametrisedWith w a -> [a]
forall a. (a -> a -> a) -> ParametrisedWith w a -> a
forall w a. Eq a => a -> ParametrisedWith w a -> Bool
forall w a. Num a => ParametrisedWith w a -> a
forall w a. Ord a => ParametrisedWith w a -> a
forall w m. Monoid m => ParametrisedWith w m -> m
forall m a. Monoid m => (a -> m) -> ParametrisedWith w a -> m
forall w a. ParametrisedWith w a -> Bool
forall w a. ParametrisedWith w a -> Int
forall w a. ParametrisedWith w a -> [a]
forall b a. (b -> a -> b) -> b -> ParametrisedWith w a -> b
forall a b. (a -> b -> b) -> b -> ParametrisedWith w a -> b
forall w a. (a -> a -> a) -> ParametrisedWith w a -> a
forall w m a. Monoid m => (a -> m) -> ParametrisedWith w a -> m
forall w b a. (b -> a -> b) -> b -> ParametrisedWith w a -> b
forall w a b. (a -> b -> b) -> b -> ParametrisedWith w a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall w m. Monoid m => ParametrisedWith w m -> m
fold :: forall m. Monoid m => ParametrisedWith w m -> m
$cfoldMap :: forall w m a. Monoid m => (a -> m) -> ParametrisedWith w a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> ParametrisedWith w a -> m
$cfoldMap' :: forall w m a. Monoid m => (a -> m) -> ParametrisedWith w a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> ParametrisedWith w a -> m
$cfoldr :: forall w a b. (a -> b -> b) -> b -> ParametrisedWith w a -> b
foldr :: forall a b. (a -> b -> b) -> b -> ParametrisedWith w a -> b
$cfoldr' :: forall w a b. (a -> b -> b) -> b -> ParametrisedWith w a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> ParametrisedWith w a -> b
$cfoldl :: forall w b a. (b -> a -> b) -> b -> ParametrisedWith w a -> b
foldl :: forall b a. (b -> a -> b) -> b -> ParametrisedWith w a -> b
$cfoldl' :: forall w b a. (b -> a -> b) -> b -> ParametrisedWith w a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> ParametrisedWith w a -> b
$cfoldr1 :: forall w a. (a -> a -> a) -> ParametrisedWith w a -> a
foldr1 :: forall a. (a -> a -> a) -> ParametrisedWith w a -> a
$cfoldl1 :: forall w a. (a -> a -> a) -> ParametrisedWith w a -> a
foldl1 :: forall a. (a -> a -> a) -> ParametrisedWith w a -> a
$ctoList :: forall w a. ParametrisedWith w a -> [a]
toList :: forall a. ParametrisedWith w a -> [a]
$cnull :: forall w a. ParametrisedWith w a -> Bool
null :: forall a. ParametrisedWith w a -> Bool
$clength :: forall w a. ParametrisedWith w a -> Int
length :: forall a. ParametrisedWith w a -> Int
$celem :: forall w a. Eq a => a -> ParametrisedWith w a -> Bool
elem :: forall a. Eq a => a -> ParametrisedWith w a -> Bool
$cmaximum :: forall w a. Ord a => ParametrisedWith w a -> a
maximum :: forall a. Ord a => ParametrisedWith w a -> a
$cminimum :: forall w a. Ord a => ParametrisedWith w a -> a
minimum :: forall a. Ord a => ParametrisedWith w a -> a
$csum :: forall w a. Num a => ParametrisedWith w a -> a
sum :: forall a. Num a => ParametrisedWith w a -> a
$cproduct :: forall w a. Num a => ParametrisedWith w a -> a
product :: forall a. Num a => ParametrisedWith w a -> a
Foldable, Functor (ParametrisedWith w)
Foldable (ParametrisedWith w)
(Functor (ParametrisedWith w), Foldable (ParametrisedWith w)) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> ParametrisedWith w a -> f (ParametrisedWith w b))
-> (forall (f :: * -> *) a.
Applicative f =>
ParametrisedWith w (f a) -> f (ParametrisedWith w a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> ParametrisedWith w a -> m (ParametrisedWith w b))
-> (forall (m :: * -> *) a.
Monad m =>
ParametrisedWith w (m a) -> m (ParametrisedWith w a))
-> Traversable (ParametrisedWith w)
forall w. Functor (ParametrisedWith w)
forall w. Foldable (ParametrisedWith w)
forall w (m :: * -> *) a.
Monad m =>
ParametrisedWith w (m a) -> m (ParametrisedWith w a)
forall w (f :: * -> *) a.
Applicative f =>
ParametrisedWith w (f a) -> f (ParametrisedWith w a)
forall w (m :: * -> *) a b.
Monad m =>
(a -> m b) -> ParametrisedWith w a -> m (ParametrisedWith w b)
forall w (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> ParametrisedWith w a -> f (ParametrisedWith w b)
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
ParametrisedWith w (m a) -> m (ParametrisedWith w a)
forall (f :: * -> *) a.
Applicative f =>
ParametrisedWith w (f a) -> f (ParametrisedWith w a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> ParametrisedWith w a -> m (ParametrisedWith w b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> ParametrisedWith w a -> f (ParametrisedWith w b)
$ctraverse :: forall w (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> ParametrisedWith w a -> f (ParametrisedWith w b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> ParametrisedWith w a -> f (ParametrisedWith w b)
$csequenceA :: forall w (f :: * -> *) a.
Applicative f =>
ParametrisedWith w (f a) -> f (ParametrisedWith w a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
ParametrisedWith w (f a) -> f (ParametrisedWith w a)
$cmapM :: forall w (m :: * -> *) a b.
Monad m =>
(a -> m b) -> ParametrisedWith w a -> m (ParametrisedWith w b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> ParametrisedWith w a -> m (ParametrisedWith w b)
$csequence :: forall w (m :: * -> *) a.
Monad m =>
ParametrisedWith w (m a) -> m (ParametrisedWith w a)
sequence :: forall (m :: * -> *) a.
Monad m =>
ParametrisedWith w (m a) -> m (ParametrisedWith w a)
Traversable, Int -> ParametrisedWith w a -> ShowS
[ParametrisedWith w a] -> ShowS
ParametrisedWith w a -> String
(Int -> ParametrisedWith w a -> ShowS)
-> (ParametrisedWith w a -> String)
-> ([ParametrisedWith w a] -> ShowS)
-> Show (ParametrisedWith w a)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall w a.
(Show a, Show w) =>
Int -> ParametrisedWith w a -> ShowS
forall w a. (Show a, Show w) => [ParametrisedWith w a] -> ShowS
forall w a. (Show a, Show w) => ParametrisedWith w a -> String
$cshowsPrec :: forall w a.
(Show a, Show w) =>
Int -> ParametrisedWith w a -> ShowS
showsPrec :: Int -> ParametrisedWith w a -> ShowS
$cshow :: forall w a. (Show a, Show w) => ParametrisedWith w a -> String
show :: ParametrisedWith w a -> String
$cshowList :: forall w a. (Show a, Show w) => [ParametrisedWith w a] -> ShowS
showList :: [ParametrisedWith w a] -> ShowS
Show)
instance (Hashable w, Hashable a) => Hashable (ParametrisedWith w a)