| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Morley.Util.Constrained
Synopsis
- data Constrained c f where
- Constrained :: forall c f a. c a => f a -> Constrained c f
- class NullConstraint any
- mapConstrained :: (forall t. c t => f t -> g t) -> Constrained c f -> Constrained c g
- traverseConstrained :: Functor m => (forall a. c a => f a -> m (g a)) -> Constrained c f -> m (Constrained c g)
- withConstrained :: Constrained c f -> (forall t. c t => f t -> r) -> r
- withConstrainedM :: Monad m => m (Constrained c f) -> (forall t. f t -> m r) -> m r
- foldConstrained :: (forall t. c t => f t -> r) -> Constrained c f -> r
- foldConstrainedM :: Monad m => (forall t. c t => f t -> m r) -> m (Constrained c f) -> m r
Documentation
data Constrained c f where Source #
Constructors
| Constrained :: forall c f a. c a => f a -> Constrained c f |
Instances
class NullConstraint any Source #
Always truthful unary constraint. Can be used to essentially turn
Constrained into a somewhat inefficient Some.
Instances
| FromJSON Address Source # | |
| FromJSONKey Address Source # | |
Defined in Morley.Tezos.Address Methods | |
| HasRPCRepr Address Source # | |
Defined in Morley.AsRPC | |
| TypeHasDoc Address Source # | |
Defined in Morley.Michelson.Typed.Haskell.Doc Associated Types type TypeDocFieldDescriptions Address :: FieldDescriptions Source # Methods typeDocName :: Proxy Address -> Text Source # typeDocMdDescription :: Markdown Source # typeDocMdReference :: Proxy Address -> WithinParens -> Markdown Source # typeDocDependencies :: Proxy Address -> [SomeDocDefinitionItem] Source # | |
| IsoValue Address Source # | |
| HasCLReader Address Source # | |
Defined in Morley.Tezos.Address | |
| NullConstraint (any :: k) Source # | |
Defined in Morley.Util.Constrained | |
| type AsRPC Address Source # | |
Defined in Morley.AsRPC | |
| type TypeDocFieldDescriptions Address Source # | |
Defined in Morley.Michelson.Typed.Haskell.Doc | |
| type ToT Address Source # | |
Defined in Morley.Michelson.Typed.Haskell.Value | |
mapConstrained :: (forall t. c t => f t -> g t) -> Constrained c f -> Constrained c g Source #
Map over argument.
traverseConstrained :: Functor m => (forall a. c a => f a -> m (g a)) -> Constrained c f -> m (Constrained c g) Source #
Traverse over argument.
withConstrained :: Constrained c f -> (forall t. c t => f t -> r) -> r Source #
Apply function to constrained value
withConstrainedM :: Monad m => m (Constrained c f) -> (forall t. f t -> m r) -> m r Source #
Monadic withConstrained
foldConstrained :: (forall t. c t => f t -> r) -> Constrained c f -> r Source #
Flipped version of withConstrained
foldConstrainedM :: Monad m => (forall t. c t => f t -> m r) -> m (Constrained c f) -> m r Source #
Flipped version of withConstrainedM