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

Morley.Michelson.Typed.Scope.Internal.ForbidT

Synopsis

Documentation

type ForbidOp Source #

Arguments

 = ForbidT 'PSOp

Convenience synonym

type family ContainsT p t where ... Source #

class ForbidManyT (ForbidT p t) '[p] t => ForbidT p t Source #

Constraint for classes forbidding type presence based on predicate defined by TPredicateSym.

Not just a type alias in order to be able to partially apply it (e.g. in Each).

Reports errors when a type does not satisfy predicate:

>>> () :: ForbidT PSOp TOperation => ()
...
... Type `operation` found in
... 'TOperation
... is not allowed in this scope
...
>>> () :: ForbidT PSContract (TContract TUnit) => ()
...
... Type `contract` found in
... 'TContract 'TUnit
... is not allowed in this scope
...
>>> () :: ForbidT PSTicket (TTicket TUnit) => ()
...
... Type `ticket` found in
... 'TTicket 'TUnit
... is not allowed in this scope
...
>>> () :: ForbidT PSBigMap (TBigMap TUnit TUnit) => ()
...
... Type `big_map` found in
... 'TBigMap 'TUnit 'TUnit
... is not allowed in this scope
...
>>> () :: ForbidT PSSaplingState (TSaplingState Z) => ()
...
... Type `sapling_state` found in
... 'TSaplingState 'Z
... is not allowed in this scope
...
>>> () :: ForbidT PSNestedBigMaps (TBigMap TUnit (TBigMap TUnit TUnit)) => ()
...
... Nested `big_map`s found in
... 'TBigMap 'TUnit ('TBigMap 'TUnit 'TUnit)
... are not allowed
...

When the type is ambiguous or polymorphic, suggests adding the corresponding constraint:

>>> (const () :: ForbidOp t => f t -> ()) undefined
...
... Can't check if type
... t0
... contains `operation`. Perhaps you need to add
... ForbidT 'PSOp t0
... constraint? You can also try adding a type annotation.
...

This constraint implies ContainsT ~ False:

>>> :{
foo :: ForbidT p t => ContainsT p t :~: False
foo = Refl
:}

Instances

Instances details
ForbidManyT (ForbidT p t) '[p] t => ForbidT p t Source # 
Instance details

Defined in Morley.Michelson.Typed.Scope.Internal.ForbidT

SingI k => WithDeMorganScope ForbidContract 'TBigMap k v Source # 
Instance details

Defined in Morley.Michelson.Typed.Scope.Internal.WithDeMorganScope

Methods

withDeMorganScope :: ForbidContract ('TBigMap k v) => ((ForbidContract k, ForbidContract v) => ret) -> ret Source #

SingI k => WithDeMorganScope ForbidOp 'TBigMap k v Source # 
Instance details

Defined in Morley.Michelson.Typed.Scope.Internal.WithDeMorganScope

Methods

withDeMorganScope :: ForbidOp ('TBigMap k v) => ((ForbidOp k, ForbidOp v) => ret) -> ret Source #

SingI k => WithDeMorganScope ForbidSaplingState 'TBigMap k v Source # 
Instance details

Defined in Morley.Michelson.Typed.Scope.Internal.WithDeMorganScope

SingI k => WithDeMorganScope ForbidTicket 'TBigMap k v Source # 
Instance details

Defined in Morley.Michelson.Typed.Scope.Internal.WithDeMorganScope

Methods

withDeMorganScope :: ForbidTicket ('TBigMap k v) => ((ForbidTicket k, ForbidTicket v) => ret) -> ret Source #

SingI t => CheckScope (ForbidBigMap t) Source # 
Instance details

Defined in Morley.Michelson.Typed.Scope.Internal.CheckScope

SingI t => CheckScope (ForbidContract t) Source # 
Instance details

Defined in Morley.Michelson.Typed.Scope.Internal.CheckScope

SingI t => CheckScope (ForbidNestedBigMaps t) Source # 
Instance details

Defined in Morley.Michelson.Typed.Scope.Internal.CheckScope

SingI t => CheckScope (ForbidOp t) Source # 
Instance details

Defined in Morley.Michelson.Typed.Scope.Internal.CheckScope

SingI t => CheckScope (ForbidSaplingState t) Source # 
Instance details

Defined in Morley.Michelson.Typed.Scope.Internal.CheckScope

SingI t => CheckScope (ForbidTicket t) Source # 
Instance details

Defined in Morley.Michelson.Typed.Scope.Internal.CheckScope

(SingI k, SingI p) => WithDeMorganScope (ForbidT p) 'TMap k v Source # 
Instance details

Defined in Morley.Michelson.Typed.Scope.Internal.WithDeMorganScope

Methods

withDeMorganScope :: ForbidT p ('TMap k v) => ((ForbidT p k, ForbidT p v) => ret) -> ret Source #

(SingI a, SingI p) => WithDeMorganScope (ForbidT p) 'TOr a b Source # 
Instance details

Defined in Morley.Michelson.Typed.Scope.Internal.WithDeMorganScope

Methods

withDeMorganScope :: ForbidT p ('TOr a b) => ((ForbidT p a, ForbidT p b) => ret) -> ret Source #

(SingI a, SingI p) => WithDeMorganScope (ForbidT p) 'TPair a b Source # 
Instance details

Defined in Morley.Michelson.Typed.Scope.Internal.WithDeMorganScope

Methods

withDeMorganScope :: ForbidT p ('TPair a b) => ((ForbidT p a, ForbidT p b) => ret) -> ret Source #

type ForbidContract Source #

Arguments

 = ForbidT 'PSContract

Convenience synonym

type ForbidTicket Source #

Arguments

 = ForbidT 'PSTicket

Convenience synonym

type ForbidBigMap Source #

Arguments

 = ForbidT 'PSBigMap

Convenience synonym

type ForbidNestedBigMaps Source #

Arguments

 = ForbidT 'PSNestedBigMaps

Convenience synonym

type ForbidNonComparable Source #

Arguments

 = ForbidT 'PSNonComparable

Convenience synonym

data TPredicateSym Source #

Type-level symbol for type predicates used in ContainsT

Constructors

PSOp

Contains operation

PSContract

Contains contract 'a

PSTicket

Contains ticket 'a

PSBigMap

Contains big_map 'k 'v

PSNestedBigMaps

Contains big_map 'k (big_map 'k 'v)

PSSaplingState

Contains sapling_state 'n

PSNonComparable

Contains non-comparable types

Instances

Instances details
SingKind TPredicateSym Source # 
Instance details

Defined in Morley.Michelson.Typed.Scope.Internal.ForbidT

Associated Types

type Demote TPredicateSym = (r :: Type) #

SDecide TPredicateSym Source # 
Instance details

Defined in Morley.Michelson.Typed.Scope.Internal.ForbidT

Methods

(%~) :: forall (a :: TPredicateSym) (b :: TPredicateSym). Sing a -> Sing b -> Decision (a :~: b) #

TestCoercion SingTPredicateSym Source # 
Instance details

Defined in Morley.Michelson.Typed.Scope.Internal.ForbidT

Methods

testCoercion :: forall (a :: k) (b :: k). SingTPredicateSym a -> SingTPredicateSym b -> Maybe (Coercion a b) #

TestEquality SingTPredicateSym Source # 
Instance details

Defined in Morley.Michelson.Typed.Scope.Internal.ForbidT

Methods

testEquality :: forall (a :: k) (b :: k). SingTPredicateSym a -> SingTPredicateSym b -> Maybe (a :~: b) #

SingI 'PSBigMap Source # 
Instance details

Defined in Morley.Michelson.Typed.Scope.Internal.ForbidT

Methods

sing :: Sing 'PSBigMap #

SingI 'PSContract Source # 
Instance details

Defined in Morley.Michelson.Typed.Scope.Internal.ForbidT

Methods

sing :: Sing 'PSContract #

SingI 'PSNestedBigMaps Source # 
Instance details

Defined in Morley.Michelson.Typed.Scope.Internal.ForbidT

SingI 'PSNonComparable Source # 
Instance details

Defined in Morley.Michelson.Typed.Scope.Internal.ForbidT

SingI 'PSOp Source # 
Instance details

Defined in Morley.Michelson.Typed.Scope.Internal.ForbidT

Methods

sing :: Sing 'PSOp #

SingI 'PSSaplingState Source # 
Instance details

Defined in Morley.Michelson.Typed.Scope.Internal.ForbidT

SingI 'PSTicket Source # 
Instance details

Defined in Morley.Michelson.Typed.Scope.Internal.ForbidT

Methods

sing :: Sing 'PSTicket #

ForbidManyT' c ps' ('[] :: [TPredicateSym]) t Source # 
Instance details

Defined in Morley.Michelson.Typed.Scope.Internal.ForbidT

Associated Types

type ForbidManySuperC '[] t Source #

(ForbidManyT' c ps' ps t, DelayedContainsTCheck c ps' p t (ContainsT p t)) => ForbidManyT' c ps' (p ': ps) t Source # 
Instance details

Defined in Morley.Michelson.Typed.Scope.Internal.ForbidT

Associated Types

type ForbidManySuperC (p ': ps) t Source #

(WhenStuck t (TypeError (ForbidManyTStuckErr c ps' t) :: Constraint), FailWhen a (ForbidTErrorMsg p t)) => DelayedContainsTCheck (c :: Constraint) (ps' :: [TPredicateSym]) (p :: TPredicateSym) (t :: T) a Source # 
Instance details

Defined in Morley.Michelson.Typed.Scope.Internal.ForbidT

type Demote TPredicateSym Source # 
Instance details

Defined in Morley.Michelson.Typed.Scope.Internal.ForbidT

type Sing Source # 
Instance details

Defined in Morley.Michelson.Typed.Scope.Internal.ForbidT

type ForbidManySuperC ('[] :: [TPredicateSym]) t Source # 
Instance details

Defined in Morley.Michelson.Typed.Scope.Internal.ForbidT

type ForbidManySuperC ('[] :: [TPredicateSym]) t = ()
type ForbidManySuperC (p ': ps) t Source # 
Instance details

Defined in Morley.Michelson.Typed.Scope.Internal.ForbidT

type ForbidManySuperC (p ': ps) t = (ContainsT p t ~ 'False, ForbidManySuperC ps t)

type family TPredicateSymTypeName p where ... Source #

Equations

TPredicateSymTypeName 'PSOp = "`operation`" 
TPredicateSymTypeName 'PSContract = "`contract`" 
TPredicateSymTypeName 'PSTicket = "`ticket`" 
TPredicateSymTypeName 'PSBigMap = "`big_map`" 
TPredicateSymTypeName 'PSNestedBigMaps = "nested `big_map`s" 
TPredicateSymTypeName 'PSSaplingState = "`sapling_state`" 
TPredicateSymTypeName 'PSNonComparable = "non-comparable types" 

type family ForbidTErrorMsg p t where ... Source #

Equations

ForbidTErrorMsg 'PSNestedBigMaps t = ('Text "Nested `big_map`s found in" ':$$: 'ShowType t) ':$$: 'Text "are not allowed" 
ForbidTErrorMsg 'PSNonComparable t = ('Text "Non-comparable type" ':$$: 'ShowType t) ':$$: 'Text "is not allowed in this scope" 
ForbidTErrorMsg p t = ((('Text "Type " ':<>: 'Text (TPredicateSymTypeName p)) ':<>: 'Text " found in") ':$$: 'ShowType t) ':$$: 'Text "is not allowed in this scope" 

type ForbidManyT c ps = ForbidManyT' c ps ps Source #

Abstracts multiple ForbidT constraints. Accepts a constraint that will be suggested in an error message in case ContainsT gets stuck. This is used with scope constraints in Morley.Michelson.Typed.Scope.Internal.Scopes.

type ForbidSaplingState Source #

Arguments

 = ForbidT 'PSSaplingState

Convenience synonym

class ForbidManySuperC ps t => ForbidManyT' c ps' ps t Source #

Class abstracting multiple ForbidT constraints.

This version accepts a custom error message displayed if ContainsT gets stuck. You likely want to use ForbidManyT, which sets this message.

It's a class and not a recursive type family because recursive type families take noticeably longer to compile.

Associated Types

type ForbidManySuperC ps t :: Constraint Source #

Instances

Instances details
ForbidManyT' c ps' ('[] :: [TPredicateSym]) t Source # 
Instance details

Defined in Morley.Michelson.Typed.Scope.Internal.ForbidT

Associated Types

type ForbidManySuperC '[] t Source #

(ForbidManyT' c ps' ps t, DelayedContainsTCheck c ps' p t (ContainsT p t)) => ForbidManyT' c ps' (p ': ps) t Source # 
Instance details

Defined in Morley.Michelson.Typed.Scope.Internal.ForbidT

Associated Types

type ForbidManySuperC (p ': ps) t Source #

class a ~ 'False => DelayedContainsTCheck c ps' p t a Source #

This is a horrible hack designed to delay GHC's test for equality of ContainsT ... with False. Unfortunately, due to the use of incoherence, more type signatures will be required downstream. But the impact seems somewhat minimal in practice.

Instances

Instances details
DelayedContainsTCheck (c :: k1) (ps' :: k2) (p :: k3) (t :: k4) 'False Source # 
Instance details

Defined in Morley.Michelson.Typed.Scope.Internal.ForbidT

(WhenStuck t (TypeError (ForbidManyTStuckErr c ps' t) :: Constraint), FailWhen a (ForbidTErrorMsg p t)) => DelayedContainsTCheck (c :: Constraint) (ps' :: [TPredicateSym]) (p :: TPredicateSym) (t :: T) a Source # 
Instance details

Defined in Morley.Michelson.Typed.Scope.Internal.ForbidT

type ForbidManyTStuckErr c ps t = ((('Text "Can't check if type" ':$$: 'ShowType t) ':$$: (('Text "contains " ':<>: TPredicateSymTypeNames ps) ':<>: 'Text ". Perhaps you need to add")) ':$$: 'ShowType c) ':$$: 'Text "constraint? You can also try adding a type annotation." Source #

type family TPredicateSymTypeNames ps where ... Source #

Given a list of TPredicateSym, pretty-print a list of corresponding type names. Uses TPredicateSymTypeName for a single type, separates the last two types with or, others with ,.

Doesn't do the oxford comma, because it's rather tricky to implement, and compilation types aren't great already.

type family PSOpSym0 :: TPredicateSym where ... Source #

Equations

PSOpSym0 = 'PSOp 

type family PSContractSym0 :: TPredicateSym where ... Source #

type family PSTicketSym0 :: TPredicateSym where ... Source #

Equations

PSTicketSym0 = 'PSTicket 

type family PSBigMapSym0 :: TPredicateSym where ... Source #

Equations

PSBigMapSym0 = 'PSBigMap