Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data ViewTyInfo = ViewTyInfo Symbol Type Type
- type family (name :: Symbol) ?:: (tys :: (Type, Type)) where ...
- type (>->) arg ret = '(arg, ret)
- data ViewsList (vl :: [ViewTyInfo])
- type family RevealViews (desc :: Type) :: [ViewTyInfo]
- type family LookupView (name :: Symbol) (views :: [ViewTyInfo]) :: (Type, Type) where ...
- type LookupRevealView name viewRef = LookupView name (RevealViews viewRef)
- type HasView vd name arg ret = LookupRevealView name vd ~ '(arg, ret)
- type family ViewsNames (vs :: [ViewTyInfo]) :: [Symbol] where ...
- newtype ViewName where
- UnsafeViewName {
- unViewName :: Text
- pattern ViewName :: Text -> ViewName
- UnsafeViewName {
- data ViewInterface = ViewInterface {}
- demoteViewName :: forall name. (KnownSymbol name, HasCallStack) => ViewName
- demoteViewTyInfos :: forall (vs :: [ViewTyInfo]). DemoteViewTyInfo vs => [ViewInterface]
- type DemoteViewsDescriptor vd = DemoteViewTyInfo (RevealViews vd)
- demoteViewsDescriptor :: forall (vd :: Type). DemoteViewTyInfo (RevealViews vd) => [ViewInterface]
- data ViewInterfaceMatchError
- = VIMViewNotFound ViewName
- | VIMViewArgMismatch (MismatchError T)
- | VIMViewRetMismatch (MismatchError T)
- checkViewsCoverInterface :: forall st. [ViewInterface] -> ViewsSet st -> Either ViewInterfaceMatchError ()
Documentation
type family (name :: Symbol) ?:: (tys :: (Type, Type)) where ... infix 3 Source #
Neat constructor for ViewTyInfo
.
type View = "view" ?:: Integer >-> Natural
name ?:: '(arg, ret) = 'ViewTyInfo name arg ret |
data ViewsList (vl :: [ViewTyInfo]) Source #
A views descriptor that directly carries the full list of views.
Instances
type RevealViews (ViewsList info) Source # | |
Defined in Lorentz.ViewBase |
type family RevealViews (desc :: Type) :: [ViewTyInfo] Source #
Get a list of views by a descriptor object.
The problem this type family solves:
it is unpleasant to carry around a list of views because it may be large,
and if we merely hide this list under a type alias, error messages will still
mention the type alias expanded.
We want e.g. Contract Parameter Storage Views
to be carried as-is.
Parameter
and Storage
are usually datatypes and they are fine, while
for Views
to be not automatically expanded we have to take special care.
You can still provide the list of ViewTyInfo
s to this type family using
ViewsList
, but generally prefer creating a dedicated datatype that would
expand to a views list.
Instances
type RevealViews () Source # | |
Defined in Lorentz.ViewBase | |
type RevealViews (ViewsList info) Source # | |
Defined in Lorentz.ViewBase |
type family LookupView (name :: Symbol) (views :: [ViewTyInfo]) :: (Type, Type) where ... Source #
Find a view in a contract by name.
LookupView name '[] = TypeError (('Text "View " ':<>: 'ShowType name) ':<>: 'Text " is not found") | |
LookupView name ('ViewTyInfo name arg ret ': _) = '(arg, ret) | |
LookupView name ('ViewTyInfo _ _ _ ': vs) = LookupView name vs |
type LookupRevealView name viewRef = LookupView name (RevealViews viewRef) Source #
Reveal views and find a view there.
type HasView vd name arg ret = LookupRevealView name vd ~ '(arg, ret) Source #
Constraint indicating that presence of the view with the specified parameters is implied by the views descriptor.
type family ViewsNames (vs :: [ViewTyInfo]) :: [Symbol] where ... Source #
Map views to get their names.
ViewsNames '[] = '[] | |
ViewsNames ('ViewTyInfo name _ _ ': vs) = name ': ViewsNames vs |
Instances
demoteViewName :: forall name. (KnownSymbol name, HasCallStack) => ViewName Source #
Demote view name from type level to term level.
demoteViewTyInfos :: forall (vs :: [ViewTyInfo]). DemoteViewTyInfo vs => [ViewInterface] Source #
Demote ViewTyInfo
s to ViewInterface
s.
type DemoteViewsDescriptor vd = DemoteViewTyInfo (RevealViews vd) Source #
demoteViewsDescriptor :: forall (vd :: Type). DemoteViewTyInfo (RevealViews vd) => [ViewInterface] Source #
Demote views descriptor to ViewInterface
s.
data ViewInterfaceMatchError Source #
VIMViewNotFound ViewName | |
VIMViewArgMismatch (MismatchError T) | |
VIMViewRetMismatch (MismatchError T) |
Instances
Exception ViewInterfaceMatchError Source # | |
Show ViewInterfaceMatchError Source # | |
Defined in Lorentz.ViewBase showsPrec :: Int -> ViewInterfaceMatchError -> ShowS # show :: ViewInterfaceMatchError -> String # showList :: [ViewInterfaceMatchError] -> ShowS # | |
Eq ViewInterfaceMatchError Source # | |
Defined in Lorentz.ViewBase | |
Buildable ViewInterfaceMatchError Source # | |
Defined in Lorentz.ViewBase build :: ViewInterfaceMatchError -> Doc buildList :: [ViewInterfaceMatchError] -> Doc |
checkViewsCoverInterface :: forall st. [ViewInterface] -> ViewsSet st -> Either ViewInterfaceMatchError () Source #
Check that the given set of views covers the given view interfaces. Extra views in the set, that do not appear in the interface, are fine.