Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- newtype UParam (entries :: [EntrypointKind]) = UnsafeUParam (MText, ByteString)
- type EntrypointKind = (Symbol, Type)
- type (?:) (n :: Symbol) (a :: k) = '(n, a)
- mkUParam :: (NicePackedValue a, LookupEntrypoint name entries ~ a, RequireUniqueEntrypoints entries) => Label name -> a -> UParam entries
- data ConstrainedSome (c :: Type -> Constraint) where
- ConstrainedSome :: c a => a -> ConstrainedSome c
- class UnpackUParam (c :: Type -> Constraint) entries
- unpackUParam :: UnpackUParam c entries => UParam entries -> Either EntrypointLookupError (MText, ConstrainedSome c)
- type SomeInterface = '['("SomeEntrypoints", Void)]
- type UParam_ = UParam SomeInterface
- type EntrypointsImpl inp out entries = Rec (CaseClauseU inp out) entries
- type UParamFallback inp out = ((MText, ByteString) : inp) :-> out
- data EntrypointLookupError
- class CaseUParam (entries :: [EntrypointKind])
- caseUParam :: (CaseUParam entries, RequireUniqueEntrypoints entries) => Rec (CaseClauseU inp out) entries -> UParamFallback inp out -> (UParam entries : inp) :-> out
- caseUParamT :: forall entries inp out clauses. (clauses ~ Rec (CaseClauseU inp out) entries, RecFromTuple clauses, CaseUParam entries) => IsoRecTuple clauses -> UParamFallback inp out -> (UParam entries : inp) :-> out
- uparamFallbackFail :: UParamFallback inp out
- type family LookupEntrypoint (name :: Symbol) (entries :: [EntrypointKind]) :: Type where ...
- type family RequireUniqueEntrypoints (entries :: [EntrypointKind]) :: Constraint where ...
- uparamFromAdt :: UParamLinearize up => up -> UParam (UParamLinearized up)
- type UParamLinearize p = (NiceGeneric p, GUParamLinearize (GRep p))
- type UParamLinearized p = GUParamLinearized (GRep p)
- pbsUParam :: forall ctorName. KnownSymbol ctorName => ParamBuildingStep
- unwrapUParam :: (UParam entries : s) :-> ((MText, ByteString) : s)
Documentation
newtype UParam (entries :: [EntrypointKind]) Source #
Encapsulates parameter for one of entry points. It keeps entrypoint name and corresponding argument serialized.
In Haskell world, we keep an invariant of that contained value relates
to one of entry points from entries
list.
Instances
type EntrypointKind = (Symbol, Type) Source #
An entrypoint is described by two types: its name and type of argument.
type (?:) (n :: Symbol) (a :: k) = '(n, a) Source #
A convenient alias for type-level name-something pair.
Construction
mkUParam :: (NicePackedValue a, LookupEntrypoint name entries ~ a, RequireUniqueEntrypoints entries) => Label name -> a -> UParam entries Source #
Construct a UParam
safely.
Deconstruction
data ConstrainedSome (c :: Type -> Constraint) where Source #
This type can store any value that satisfies a certain constraint.
ConstrainedSome :: c a => a -> ConstrainedSome c |
Instances
Show (ConstrainedSome Show) Source # | |
Defined in Lorentz.UParam | |
Buildable (ConstrainedSome Buildable) Source # | |
Defined in Lorentz.UParam build :: ConstrainedSome Buildable -> Doc buildList :: [ConstrainedSome Buildable] -> Doc |
class UnpackUParam (c :: Type -> Constraint) entries Source #
This class is needed to implement unpackUParam
.
Instances
UnpackUParam c ('[] :: [EntrypointKind]) Source # | |
Defined in Lorentz.UParam unpackUParam :: UParam '[] -> Either EntrypointLookupError (MText, ConstrainedSome c) Source # | |
(KnownSymbol name, UnpackUParam c entries, NiceUnpackedValue arg, c arg) => UnpackUParam c ((name ?: arg) ': entries) Source # | |
Defined in Lorentz.UParam unpackUParam :: UParam ((name ?: arg) ': entries) -> Either EntrypointLookupError (MText, ConstrainedSome c) Source # |
unpackUParam :: UnpackUParam c entries => UParam entries -> Either EntrypointLookupError (MText, ConstrainedSome c) Source #
Turn UParam
into a Haskell value.
Since we don't know its type in compile time, we have to erase it using
ConstrainedSome
. The user of this function can require arbitrary
constraint to hold (depending on how they want to use the result).
Casting to homomorphic value
type SomeInterface = '['("SomeEntrypoints", Void)] Source #
Pseudo value for UParam
type variable.
type UParam_ = UParam SomeInterface Source #
Homomorphic version of UParam
, forgets the exact interface.
Pattern-matching
type EntrypointsImpl inp out entries = Rec (CaseClauseU inp out) entries Source #
Implementations of some entry points.
Note that this thing inherits properties of Rec
, e.g. you can
Data.Vinyl.Core.rappend
implementations for two entrypoint sets
when assembling scattered parts of a contract.
type UParamFallback inp out = ((MText, ByteString) : inp) :-> out Source #
An action invoked when user-provided entrypoint is not found.
data EntrypointLookupError Source #
Instances
class CaseUParam (entries :: [EntrypointKind]) Source #
Make up a "case" over entry points.
unsafeCaseUParam
Instances
CaseUParam ('[] :: [EntrypointKind]) Source # | |
Defined in Lorentz.UParam unsafeCaseUParam :: forall (inp :: [Type]) (out :: [Type]). Rec (CaseClauseU inp out) '[] -> UParamFallback inp out -> (UParam '[] ': inp) :-> out | |
(KnownSymbol name, CaseUParam entries, Typeable entries, NiceUnpackedValue arg) => CaseUParam ((name ?: arg) ': entries) Source # | |
Defined in Lorentz.UParam unsafeCaseUParam :: forall (inp :: [Type]) (out :: [Type]). Rec (CaseClauseU inp out) ((name ?: arg) ': entries) -> UParamFallback inp out -> (UParam ((name ?: arg) ': entries) ': inp) :-> out |
caseUParam :: (CaseUParam entries, RequireUniqueEntrypoints entries) => Rec (CaseClauseU inp out) entries -> UParamFallback inp out -> (UParam entries : inp) :-> out Source #
Pattern-match on given UParam entries
.
You have to provide all case branches and a fallback action on case when entrypoint is not found.
caseUParamT :: forall entries inp out clauses. (clauses ~ Rec (CaseClauseU inp out) entries, RecFromTuple clauses, CaseUParam entries) => IsoRecTuple clauses -> UParamFallback inp out -> (UParam entries : inp) :-> out Source #
Like caseUParam
, but accepts a tuple of clauses, not a Rec
.
uparamFallbackFail :: UParamFallback inp out Source #
Default implementation for UParamFallback
, simply reports an error.
Constraints
type family LookupEntrypoint (name :: Symbol) (entries :: [EntrypointKind]) :: Type where ... Source #
Get type of entrypoint argument by its name.
LookupEntrypoint name ('(name, a) ': _) = a | |
LookupEntrypoint name (_ ': entries) = LookupEntrypoint name entries | |
LookupEntrypoint name '[] = TypeError (('Text "Entry point " ':<>: 'ShowType name) ':<>: 'Text " in not in the entry points list") |
type family RequireUniqueEntrypoints (entries :: [EntrypointKind]) :: Constraint where ... Source #
Ensure that given entry points do no contain duplicated names.
RequireUniqueEntrypoints entries = RequireAllUnique "entrypoint" (Eval (Map Fst entries)) |
Conversion from ADT
uparamFromAdt :: UParamLinearize up => up -> UParam (UParamLinearized up) Source #
Make up UParam
from ADT sum.
Entry points template will consist of
(constructorName, constructorFieldType)
pairs.
Each constructor is expected to have exactly one field.
Shows human-readable errors when up
is stuck.
>>>
data Foo = Foo ()
>>>
uparamFromAdt $ Foo ()
... ... GHC.Generics.Rep Foo ... is stuck. Likely ... Generic Foo ... instance is missing or out of scope. ...
>>>
data Foo = Foo () deriving Generic
>>>
uparamFromAdt $ Foo ()
UnsafeUParam (UnsafeMText {unMText = "Foo"},"\ENQ\ETX\v")
type UParamLinearize p = (NiceGeneric p, GUParamLinearize (GRep p)) Source #
Constraint required by uparamFromAdt
.
type UParamLinearized p = GUParamLinearized (GRep p) Source #
Entry points template derived from given ADT sum.
Documentation
pbsUParam :: forall ctorName. KnownSymbol ctorName => ParamBuildingStep Source #
Note that calling given entrypoints involves constructing UParam
.
Internals used for entrypoint-wise migrations
unwrapUParam :: (UParam entries : s) :-> ((MText, ByteString) : s) Source #
Helper instruction which extracts content of UParam
.
Orphan instances
CustomErrorHasDoc "uparamArgumentUnpackFailed" Source # | |
CustomErrorHasDoc "uparamNoSuchEntrypoint" Source # | |
Buildable (CustomError "uparamArgumentUnpackFailed") Source # | |
build :: CustomError "uparamArgumentUnpackFailed" -> Doc buildList :: [CustomError "uparamArgumentUnpackFailed"] -> Doc | |
Buildable (CustomError "uparamNoSuchEntrypoint") Source # | |
build :: CustomError "uparamNoSuchEntrypoint" -> Doc buildList :: [CustomError "uparamNoSuchEntrypoint"] -> Doc |