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

Morley.Michelson.Untyped.View

Contents

Description

Michelson view.

Synopsis

Documentation

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)))

mkViewName :: Text -> Either BadViewNameError ViewName Source #

Construct ViewName performing all the checks.

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)))

isValidViewNameChar :: Char -> Bool Source #

Whether the given character is valid for a view.

viewNameMaxLength :: Int Source #

Maximum allowed name length for a view.

viewNameToMText :: ViewName -> MText Source #

Valid view names form a subset of valid Michelson texts.

data View' op Source #

Untyped view in a contract.

Constructors

View 

Fields

Instances

Instances details
Functor View' Source # 
Instance details

Defined in Morley.Michelson.Untyped.View

Methods

fmap :: (a -> b) -> View' a -> View' b #

(<$) :: a -> View' b -> View' a #

FromJSON op => FromJSON (View' op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.View

ToJSON op => ToJSON (View' op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.View

Data op => Data (View' op) Source # 
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) -> View' op -> c (View' op) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (View' op) #

toConstr :: View' op -> Constr #

dataTypeOf :: View' op -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> View' op -> View' op #

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

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

gmapQ :: (forall d. Data d => d -> u) -> View' op -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> View' op -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> View' op -> m (View' op) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> View' op -> m (View' op) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> View' op -> m (View' op) #

Generic (View' op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.View

Associated Types

type Rep (View' op) :: Type -> Type #

Methods

from :: View' op -> Rep (View' op) x #

to :: Rep (View' op) x -> View' op #

Show op => Show (View' op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.View

Methods

showsPrec :: Int -> View' op -> ShowS #

show :: View' op -> String #

showList :: [View' op] -> ShowS #

NFData op => NFData (View' op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.View

Methods

rnf :: View' op -> () #

Eq op => Eq (View' op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.View

Methods

(==) :: View' op -> View' op -> Bool #

(/=) :: View' op -> View' op -> Bool #

type Rep (View' op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.View

type Rep (View' op) = D1 ('MetaData "View'" "Morley.Michelson.Untyped.View" "morley-1.20.0-inplace" 'False) (C1 ('MetaCons "View" 'PrefixI 'True) ((S1 ('MetaSel ('Just "viewName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ViewName) :*: S1 ('MetaSel ('Just "viewArgument") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Ty)) :*: (S1 ('MetaSel ('Just "viewReturn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Ty) :*: S1 ('MetaSel ('Just "viewCode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 op))))

newtype ViewsSet instr Source #

Constructors

ViewsSet 

Fields

Instances

Instances details
Functor ViewsSet Source # 
Instance details

Defined in Morley.Michelson.Untyped.View

Methods

fmap :: (a -> b) -> ViewsSet a -> ViewsSet b #

(<$) :: a -> ViewsSet b -> ViewsSet a #

FromJSON instr => FromJSON (ViewsSet instr) Source # 
Instance details

Defined in Morley.Michelson.Untyped.View

Methods

parseJSON :: Value -> Parser (ViewsSet instr) #

parseJSONList :: Value -> Parser [ViewsSet instr] #

ToJSON instr => ToJSON (ViewsSet instr) Source # 
Instance details

Defined in Morley.Michelson.Untyped.View

Methods

toJSON :: ViewsSet instr -> Value #

toEncoding :: ViewsSet instr -> Encoding #

toJSONList :: [ViewsSet instr] -> Value #

toEncodingList :: [ViewsSet instr] -> Encoding #

Data instr => Data (ViewsSet instr) Source # 
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) -> ViewsSet instr -> c (ViewsSet instr) #

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

toConstr :: ViewsSet instr -> Constr #

dataTypeOf :: ViewsSet instr -> DataType #

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

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

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

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

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

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

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

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

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

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

Show instr => Show (ViewsSet instr) Source # 
Instance details

Defined in Morley.Michelson.Untyped.View

Methods

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

show :: ViewsSet instr -> String #

showList :: [ViewsSet instr] -> ShowS #

Default (ViewsSet instr) Source # 
Instance details

Defined in Morley.Michelson.Untyped.View

Methods

def :: ViewsSet instr #

NFData instr => NFData (ViewsSet instr) Source # 
Instance details

Defined in Morley.Michelson.Untyped.View

Methods

rnf :: ViewsSet instr -> () #

Eq instr => Eq (ViewsSet instr) Source # 
Instance details

Defined in Morley.Michelson.Untyped.View

Methods

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

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

Container (ViewsSet instr) Source # 
Instance details

Defined in Morley.Michelson.Untyped.View

Associated Types

type Element (ViewsSet instr) #

Methods

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

null :: ViewsSet instr -> Bool #

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

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

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

length :: ViewsSet instr -> Int #

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

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

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

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

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

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

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

and :: ViewsSet instr -> Bool #

or :: ViewsSet instr -> Bool #

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

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

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

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

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

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

type Element (ViewsSet instr) Source # 
Instance details

Defined in Morley.Michelson.Untyped.View

type Element (ViewsSet instr) = Element (Map ViewName (View' instr))

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

Manipulation

emptyViewsSet :: forall instr. ViewsSet instr Source #

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

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