morley-1.19.0: Developer tools for the Michelson Language
Safe HaskellSafe-Inferred
LanguageHaskell2010

Morley.Util.Constrained

Synopsis

Documentation

data Constrained c f where Source #

Constructors

Constrained :: forall c f a. c a => f a -> Constrained c f 

Instances

Instances details
FromJSON Address Source # 
Instance details

Defined in Morley.Tezos.Address

FromJSONKey Address Source # 
Instance details

Defined in Morley.Tezos.Address

HasRPCRepr Address Source # 
Instance details

Defined in Morley.AsRPC

Associated Types

type AsRPC Address Source #

TypeHasDoc Address Source # 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

IsoValue Address Source # 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT Address :: T Source #

(forall (a :: k). c a => Lift (f a)) => Lift (Constrained c f :: Type) Source # 
Instance details

Defined in Morley.Util.Constrained

Methods

lift :: Quote m => Constrained c f -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Constrained c f -> Code m (Constrained c f) #

SingI kinds => FromJSON (ConstrainedAddress kinds) Source # 
Instance details

Defined in Morley.Tezos.Address

(forall (t :: T). cs t => HasNoOp t) => RenderDoc (SomeConstrainedValue cs) Source # 
Instance details

Defined in Morley.Michelson.Typed.Existential

ToJSON (Constrained c KindedAddress) Source # 
Instance details

Defined in Morley.Tezos.Address

ToJSONKey (Constrained c KindedAddress) Source # 
Instance details

Defined in Morley.Tezos.Address

(forall (a :: k). c a => Show (f a)) => Show (Constrained c f) Source # 
Instance details

Defined in Morley.Util.Constrained

Methods

showsPrec :: Int -> Constrained c f -> ShowS #

show :: Constrained c f -> String #

showList :: [Constrained c f] -> ShowS #

(forall (a :: k). c a => NFData (f a)) => NFData (Constrained c f) Source # 
Instance details

Defined in Morley.Util.Constrained

Methods

rnf :: Constrained c f -> () #

(forall (a :: k). c a => Buildable (f a)) => Buildable (Constrained c f) Source # 
Instance details

Defined in Morley.Util.Constrained

Methods

build :: Constrained c f -> Builder #

GEq f => Eq (Constrained c f) Source # 
Instance details

Defined in Morley.Util.Constrained

Methods

(==) :: Constrained c f -> Constrained c f -> Bool #

(/=) :: Constrained c f -> Constrained c f -> Bool #

GCompare f => Ord (Constrained c f) Source # 
Instance details

Defined in Morley.Util.Constrained

Methods

compare :: Constrained c f -> Constrained c f -> Ordering #

(<) :: Constrained c f -> Constrained c f -> Bool #

(<=) :: Constrained c f -> Constrained c f -> Bool #

(>) :: Constrained c f -> Constrained c f -> Bool #

(>=) :: Constrained c f -> Constrained c f -> Bool #

max :: Constrained c f -> Constrained c f -> Constrained c f #

min :: Constrained c f -> Constrained c f -> Constrained c f #

type AsRPC Address Source # 
Instance details

Defined in Morley.AsRPC

type TypeDocFieldDescriptions Address Source # 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

type ToT Address Source # 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

class NullConstraint any Source #

Always truthful unary constraint. Can be used to essentially turn Constrained into a somewhat inefficient Some.

Instances

Instances details
FromJSON Address Source # 
Instance details

Defined in Morley.Tezos.Address

FromJSONKey Address Source # 
Instance details

Defined in Morley.Tezos.Address

HasRPCRepr Address Source # 
Instance details

Defined in Morley.AsRPC

Associated Types

type AsRPC Address Source #

TypeHasDoc Address Source # 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

IsoValue Address Source # 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT Address :: T Source #

NullConstraint (any :: k) Source # 
Instance details

Defined in Morley.Util.Constrained

type AsRPC Address Source # 
Instance details

Defined in Morley.AsRPC

type TypeDocFieldDescriptions Address Source # 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

type ToT Address Source # 
Instance details

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 #

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