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

Morley.Michelson.Typed.View

Description

Module, containing on-chain views declarations.

Synopsis

View

newtype ViewName Source #

Name of the view.

  1. It must not exceed 31 chars length;
  2. Must use [a-zA-Z0-9_.%@] charset.

Constructors

UnsafeViewName 

Fields

Bundled Patterns

pattern ViewName :: Text -> ViewName 

Instances

Instances details
FromJSON ViewName Source # 
Instance details

Defined in Morley.Michelson.Internal.ViewName

FromJSONKey ViewName Source # 
Instance details

Defined in Morley.Michelson.Internal.ViewName

ToJSON ViewName Source # 
Instance details

Defined in Morley.Michelson.Internal.ViewName

ToJSONKey ViewName Source # 
Instance details

Defined in Morley.Michelson.Internal.ViewName

Data ViewName Source # 
Instance details

Defined in Morley.Michelson.Internal.ViewName

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 #

Generic ViewName Source # 
Instance details

Defined in Morley.Michelson.Internal.ViewName

Associated Types

type Rep ViewName :: Type -> Type #

Methods

from :: ViewName -> Rep ViewName x #

to :: Rep ViewName x -> ViewName #

Show ViewName Source # 
Instance details

Defined in Morley.Michelson.Internal.ViewName

NFData ViewName Source # 
Instance details

Defined in Morley.Michelson.Internal.ViewName

Methods

rnf :: ViewName -> () #

Eq ViewName Source # 
Instance details

Defined in Morley.Michelson.Internal.ViewName

Ord ViewName Source # 
Instance details

Defined in Morley.Michelson.Internal.ViewName

ToExpression ViewName Source # 
Instance details

Defined in Morley.Micheline.Class

RenderDoc ViewName Source # 
Instance details

Defined in Morley.Michelson.Internal.ViewName

HasCLReader ViewName Source # 
Instance details

Defined in Morley.Michelson.Internal.ViewName

Buildable ViewName Source # 
Instance details

Defined in Morley.Michelson.Internal.ViewName

Methods

build :: ViewName -> Doc

buildList :: [ViewName] -> Doc

FromExp x ViewName Source # 
Instance details

Defined in Morley.Micheline.Class

type Rep ViewName Source # 
Instance details

Defined in Morley.Michelson.Internal.ViewName

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

data BadViewNameError Source #

Instances

Instances details
Data BadViewNameError Source # 
Instance details

Defined in Morley.Michelson.Internal.ViewName

Methods

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

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

toConstr :: BadViewNameError -> Constr #

dataTypeOf :: BadViewNameError -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic BadViewNameError Source # 
Instance details

Defined in Morley.Michelson.Internal.ViewName

Associated Types

type Rep BadViewNameError :: Type -> Type #

Show BadViewNameError Source # 
Instance details

Defined in Morley.Michelson.Internal.ViewName

NFData BadViewNameError Source # 
Instance details

Defined in Morley.Michelson.Internal.ViewName

Methods

rnf :: BadViewNameError -> () #

Eq BadViewNameError Source # 
Instance details

Defined in Morley.Michelson.Internal.ViewName

Ord BadViewNameError Source # 
Instance details

Defined in Morley.Michelson.Internal.ViewName

Buildable BadViewNameError Source # 
Instance details

Defined in Morley.Michelson.Internal.ViewName

Methods

build :: BadViewNameError -> Doc

buildList :: [BadViewNameError] -> Doc

type Rep BadViewNameError Source # 
Instance details

Defined in Morley.Michelson.Internal.ViewName

type Rep BadViewNameError = D1 ('MetaData "BadViewNameError" "Morley.Michelson.Internal.ViewName" "morley-1.20.0-inplace" 'False) (C1 ('MetaCons "BadViewTooLong" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int)) :+: C1 ('MetaCons "BadViewIllegalChars" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text)))

mkViewName :: Text -> Either BadViewNameError ViewName Source #

Construct ViewName performing all the checks.

viewNameToMText :: ViewName -> MText Source #

Valid view names form a subset of valid Michelson texts.

type ViewCode' instr arg st ret = instr '['TPair arg st] '[ret] Source #

data View' instr arg st ret Source #

Contract view.

Constructors

(ViewableScope arg, SingI st, ViewableScope ret) => View 

Fields

Instances

Instances details
Show (ViewCode' instr arg st ret) => Show (View' instr arg st ret) Source # 
Instance details

Defined in Morley.Michelson.Typed.View

Methods

showsPrec :: Int -> View' instr arg st ret -> ShowS #

show :: View' instr arg st ret -> String #

showList :: [View' instr arg st ret] -> ShowS #

NFData (ViewCode' instr arg st ret) => NFData (View' instr arg st ret) Source # 
Instance details

Defined in Morley.Michelson.Typed.View

Methods

rnf :: View' instr arg st ret -> () #

Eq (ViewCode' instr arg st ret) => Eq (View' instr arg st ret) Source # 
Instance details

Defined in Morley.Michelson.Typed.View

Methods

(==) :: View' instr arg st ret -> View' instr arg st ret -> Bool #

(/=) :: View' instr arg st ret -> View' instr arg st ret -> Bool #

data SomeView' instr st where Source #

Constructors

SomeView :: View' instr arg st ret -> SomeView' instr st 

Instances

Instances details
(forall (arg :: T) (ret :: T). Show (ViewCode' instr arg st ret)) => Show (SomeView' instr st) Source # 
Instance details

Defined in Morley.Michelson.Typed.View

Methods

showsPrec :: Int -> SomeView' instr st -> ShowS #

show :: SomeView' instr st -> String #

showList :: [SomeView' instr st] -> ShowS #

(forall (arg :: T) (ret :: T). NFData (ViewCode' instr arg st ret)) => NFData (SomeView' instr st) Source # 
Instance details

Defined in Morley.Michelson.Typed.View

Methods

rnf :: SomeView' instr st -> () #

(forall (arg :: T) (ret :: T). Eq (ViewCode' instr arg st ret)) => Eq (SomeView' instr st) Source # 
Instance details

Defined in Morley.Michelson.Typed.View

Methods

(==) :: SomeView' instr st -> SomeView' instr st -> Bool #

(/=) :: SomeView' instr st -> SomeView' instr st -> Bool #

someViewName :: SomeView' instr st -> ViewName Source #

Obtain the name of the view.

Views set

newtype ViewsSet' instr st Source #

Views that belong to one contract.

Constructors

ViewsSet 

Fields

Bundled Patterns

pattern ViewsList :: [SomeView' instr st] -> ViewsSet' instr st 

Instances

Instances details
(forall (i :: [T]) (o :: [T]). Show (instr i o)) => Show (ViewsSet' instr st) Source # 
Instance details

Defined in Morley.Michelson.Typed.View

Methods

showsPrec :: Int -> ViewsSet' instr st -> ShowS #

show :: ViewsSet' instr st -> String #

showList :: [ViewsSet' instr st] -> ShowS #

Default (ViewsSet' instr st) Source # 
Instance details

Defined in Morley.Michelson.Typed.View

Methods

def :: ViewsSet' instr st #

(forall (i :: [T]) (o :: [T]). NFData (instr i o)) => NFData (ViewsSet' instr st) Source # 
Instance details

Defined in Morley.Michelson.Typed.View

Methods

rnf :: ViewsSet' instr st -> () #

(forall (i :: [T]) (o :: [T]). Eq (instr i o)) => Eq (ViewsSet' instr st) Source # 
Instance details

Defined in Morley.Michelson.Typed.View

Methods

(==) :: ViewsSet' instr st -> ViewsSet' instr st -> Bool #

(/=) :: ViewsSet' instr st -> ViewsSet' instr st -> Bool #

Container (ViewsSet' instr st) Source # 
Instance details

Defined in Morley.Michelson.Typed.View

Associated Types

type Element (ViewsSet' instr st) #

Methods

toList :: ViewsSet' instr st -> [Element (ViewsSet' instr st)] #

null :: ViewsSet' instr st -> Bool #

foldr :: (Element (ViewsSet' instr st) -> b -> b) -> b -> ViewsSet' instr st -> b #

foldl :: (b -> Element (ViewsSet' instr st) -> b) -> b -> ViewsSet' instr st -> b #

foldl' :: (b -> Element (ViewsSet' instr st) -> b) -> b -> ViewsSet' instr st -> b #

length :: ViewsSet' instr st -> Int #

elem :: Element (ViewsSet' instr st) -> ViewsSet' instr st -> Bool #

foldMap :: Monoid m => (Element (ViewsSet' instr st) -> m) -> ViewsSet' instr st -> m #

fold :: ViewsSet' instr st -> Element (ViewsSet' instr st) #

foldr' :: (Element (ViewsSet' instr st) -> b -> b) -> b -> ViewsSet' instr st -> b #

notElem :: Element (ViewsSet' instr st) -> ViewsSet' instr st -> Bool #

all :: (Element (ViewsSet' instr st) -> Bool) -> ViewsSet' instr st -> Bool #

any :: (Element (ViewsSet' instr st) -> Bool) -> ViewsSet' instr st -> Bool #

and :: ViewsSet' instr st -> Bool #

or :: ViewsSet' instr st -> Bool #

find :: (Element (ViewsSet' instr st) -> Bool) -> ViewsSet' instr st -> Maybe (Element (ViewsSet' instr st)) #

safeHead :: ViewsSet' instr st -> Maybe (Element (ViewsSet' instr st)) #

safeMaximum :: ViewsSet' instr st -> Maybe (Element (ViewsSet' instr st)) #

safeMinimum :: ViewsSet' instr st -> Maybe (Element (ViewsSet' instr st)) #

safeFoldr1 :: (Element (ViewsSet' instr st) -> Element (ViewsSet' instr st) -> Element (ViewsSet' instr st)) -> ViewsSet' instr st -> Maybe (Element (ViewsSet' instr st)) #

safeFoldl1 :: (Element (ViewsSet' instr st) -> Element (ViewsSet' instr st) -> Element (ViewsSet' instr st)) -> ViewsSet' instr st -> Maybe (Element (ViewsSet' instr st)) #

type Element (ViewsSet' instr st) Source # 
Instance details

Defined in Morley.Michelson.Typed.View

type Element (ViewsSet' instr st) = Element (Map ViewName (SomeView' instr st))

data ViewsSetError Source #

Errors possible when constructing ViewsSet.

Instances

Instances details
Show ViewsSetError Source # 
Instance details

Defined in Morley.Michelson.Internal.ViewsSet

Eq ViewsSetError Source # 
Instance details

Defined in Morley.Michelson.Internal.ViewsSet

Buildable ViewsSetError Source # 
Instance details

Defined in Morley.Michelson.Internal.ViewsSet

Methods

build :: ViewsSetError -> Doc

buildList :: [ViewsSetError] -> Doc

mkViewsSet :: [SomeView' instr st] -> Either ViewsSetError (ViewsSet' instr st) Source #

Construct views set.

emptyViewsSet :: forall instr st. ViewsSet' instr st Source #

No views.

addViewToSet :: View' instr arg st ret -> ViewsSet' instr st -> Either ViewsSetError (ViewsSet' instr st) Source #

Add a view to set.

lookupView :: forall instr st. ViewName -> ViewsSet' instr st -> Maybe (SomeView' instr st) Source #

Find a view in the set.

viewsSetNames :: forall instr st. ViewsSet' instr st -> Set ViewName Source #

Get all taken names in views set.

data SomeViewsSet' instr where Source #

Constructors

SomeViewsSet :: SingI st => ViewsSet' instr st -> SomeViewsSet' instr 

Instances

Instances details
(forall (i :: [T]) (o :: [T]). Show (instr i o)) => Show (SomeViewsSet' instr) Source # 
Instance details

Defined in Morley.Michelson.Typed.View

Methods

showsPrec :: Int -> SomeViewsSet' instr -> ShowS #

show :: SomeViewsSet' instr -> String #

showList :: [SomeViewsSet' instr] -> ShowS #

(forall (i :: [T]) (o :: [T]). NFData (instr i o)) => NFData (SomeViewsSet' instr) Source # 
Instance details

Defined in Morley.Michelson.Typed.View

Methods

rnf :: SomeViewsSet' instr -> () #

(forall (i :: [T]) (o :: [T]). Eq (instr i o)) => Eq (SomeViewsSet' instr) Source # 
Instance details

Defined in Morley.Michelson.Typed.View

Methods

(==) :: SomeViewsSet' instr -> SomeViewsSet' instr -> Bool #

(/=) :: SomeViewsSet' instr -> SomeViewsSet' instr -> Bool #