lorentz-0.13.1: EDSL for the Michelson Language
Safe HaskellNone
LanguageHaskell2010

Lorentz.ViewBase

Synopsis

Documentation

data ViewTyInfo Source #

Type-level information about a view.

Constructors

ViewTyInfo Symbol Type Type 

type family (name :: Symbol) ?:: (tys :: (Type, Type)) where ... infix 3 Source #

Neat constructor for ViewTyInfo.

type View = "view" ?:: Integer >-> Natural

Equations

name ?:: '(arg, ret) = 'ViewTyInfo name arg ret 

type (>->) arg ret = '(arg, ret) infix 5 Source #

data ViewsList (vl :: [ViewTyInfo]) Source #

A views descriptor that directly carries the full list of views.

Instances

Instances details
type RevealViews (ViewsList info) Source # 
Instance details

Defined in Lorentz.ViewBase

type RevealViews (ViewsList info) = info

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 ViewTyInfos to this type family using ViewsList, but generally prefer creating a dedicated datatype that would expand to a views list.

Instances

Instances details
type RevealViews () Source # 
Instance details

Defined in Lorentz.ViewBase

type RevealViews () = '[] :: [ViewTyInfo]
type RevealViews (ViewsList info) Source # 
Instance details

Defined in Lorentz.ViewBase

type RevealViews (ViewsList info) = info

type family LookupView (name :: Symbol) (views :: [ViewTyInfo]) :: (Type, Type) where ... Source #

Find a view in a contract by name.

Equations

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.

Equations

ViewsNames '[] = '[] 
ViewsNames ('ViewTyInfo name _ _ ': vs) = name ': ViewsNames vs 

newtype ViewName #

Constructors

UnsafeViewName 

Fields

Bundled Patterns

pattern ViewName :: Text -> ViewName 

Instances

Instances details
Eq ViewName 
Instance details

Defined in Morley.Michelson.Untyped.View

Data ViewName 
Instance details

Defined in Morley.Michelson.Untyped.View

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ViewName -> c ViewName #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ViewName #

toConstr :: ViewName -> Constr #

dataTypeOf :: ViewName -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ViewName) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ViewName) #

gmapT :: (forall b. Data b => b -> b) -> ViewName -> ViewName #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ViewName -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ViewName -> r #

gmapQ :: (forall d. Data d => d -> u) -> ViewName -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ViewName -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ViewName -> m ViewName #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ViewName -> m ViewName #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ViewName -> m ViewName #

Ord ViewName 
Instance details

Defined in Morley.Michelson.Untyped.View

Show ViewName 
Instance details

Defined in Morley.Michelson.Untyped.View

Generic ViewName 
Instance details

Defined in Morley.Michelson.Untyped.View

Associated Types

type Rep ViewName :: Type -> Type #

Methods

from :: ViewName -> Rep ViewName x #

to :: Rep ViewName x -> ViewName #

ToJSON ViewName 
Instance details

Defined in Morley.Michelson.Untyped.View

FromJSON ViewName 
Instance details

Defined in Morley.Michelson.Untyped.View

NFData ViewName 
Instance details

Defined in Morley.Michelson.Untyped.View

Methods

rnf :: ViewName -> () #

Buildable ViewName 
Instance details

Defined in Morley.Michelson.Untyped.View

Methods

build :: ViewName -> Builder #

RenderDoc ViewName 
Instance details

Defined in Morley.Michelson.Untyped.View

Methods

renderDoc :: RenderContext -> ViewName -> Doc

isRenderable :: ViewName -> Bool

FromExpression ViewName 
Instance details

Defined in Morley.Micheline.Class

Methods

fromExpression :: Expression -> Either FromExpressionError ViewName

ToExpression ViewName 
Instance details

Defined in Morley.Micheline.Class

Methods

toExpression :: ViewName -> Expression

type Rep ViewName 
Instance details

Defined in Morley.Michelson.Untyped.View

type Rep ViewName = D1 ('MetaData "ViewName" "Morley.Michelson.Untyped.View" "morley-1.16.1-inplace" 'True) (C1 ('MetaCons "UnsafeViewName" 'PrefixI 'True) (S1 ('MetaSel ('Just "unViewName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data ViewInterface Source #

Interface of a single view at term-level.

Constructors

ViewInterface 

Fields

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 #

type DemoteViewsDescriptor vd = DemoteViewTyInfo (RevealViews vd) Source #

demoteViewsDescriptor :: forall (vd :: Type). DemoteViewTyInfo (RevealViews vd) => [ViewInterface] Source #

Demote views descriptor to ViewInterfaces.

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.