morley-1.0.0: Developer tools for the Michelson Language

Safe HaskellNone
LanguageHaskell2010

Michelson.Untyped.Annotation

Description

Michelson annotations in untyped model.

Synopsis

Documentation

newtype Annotation tag Source #

Generic TypeFieldVariable Annotation

As per Michelson documentation, this type has an invariant: (except for the first character, here parametrized in the type tag) the allowed character set is the one matching the following regexp: %|%%|%|[:%][_a-zA-Z][_0-9a-zA-Z.%@]*

Constructors

AnnotationUnsafe 

Fields

Instances
Semigroup VarAnn Source # 
Instance details

Defined in Michelson.Untyped.Annotation

Monoid VarAnn Source # 
Instance details

Defined in Michelson.Untyped.Annotation

Functor (Annotation :: Type -> Type) Source # 
Instance details

Defined in Michelson.Untyped.Annotation

Methods

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

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

Eq (Annotation tag) Source # 
Instance details

Defined in Michelson.Untyped.Annotation

Methods

(==) :: Annotation tag -> Annotation tag -> Bool #

(/=) :: Annotation tag -> Annotation tag -> Bool #

(Typeable tag, Typeable k) => Data (Annotation tag) Source # 
Instance details

Defined in Michelson.Untyped.Annotation

Methods

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

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

toConstr :: Annotation tag -> Constr #

dataTypeOf :: Annotation tag -> DataType #

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

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

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

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

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

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

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

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

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

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

KnownAnnTag tag => Show (Annotation tag) Source # 
Instance details

Defined in Michelson.Untyped.Annotation

Methods

showsPrec :: Int -> Annotation tag -> ShowS #

show :: Annotation tag -> String #

showList :: [Annotation tag] -> ShowS #

IsString (Annotation tag) Source # 
Instance details

Defined in Michelson.Untyped.Annotation

Methods

fromString :: String -> Annotation tag #

Generic (Annotation tag) Source # 
Instance details

Defined in Michelson.Untyped.Annotation

Associated Types

type Rep (Annotation tag) :: Type -> Type #

Methods

from :: Annotation tag -> Rep (Annotation tag) x #

to :: Rep (Annotation tag) x -> Annotation tag #

Lift (Annotation tag) Source # 
Instance details

Defined in Michelson.Untyped.Annotation

Methods

lift :: Annotation tag -> Q Exp #

Arbitrary (Annotation tag) Source # 
Instance details

Defined in Util.Test.Arbitrary

Methods

arbitrary :: Gen (Annotation tag) #

shrink :: Annotation tag -> [Annotation tag] #

ToJSON (Annotation tag) Source # 
Instance details

Defined in Michelson.Untyped.Annotation

FromJSON (Annotation tag) Source # 
Instance details

Defined in Michelson.Untyped.Annotation

Default (Annotation tag) Source # 
Instance details

Defined in Michelson.Untyped.Annotation

Methods

def :: Annotation tag #

KnownAnnTag tag => Buildable (Annotation tag) Source # 
Instance details

Defined in Michelson.Untyped.Annotation

Methods

build :: Annotation tag -> Builder #

ToADTArbitrary (Annotation tag) Source # 
Instance details

Defined in Util.Test.Arbitrary

KnownAnnTag tag => RenderDoc (Annotation tag) Source # 
Instance details

Defined in Michelson.Untyped.Annotation

type Rep (Annotation tag) Source # 
Instance details

Defined in Michelson.Untyped.Annotation

type Rep (Annotation tag) = D1 (MetaData "Annotation" "Michelson.Untyped.Annotation" "morley-1.0.0-Jo9z4xumEmKBIsSgg9Z0MH" True) (C1 (MetaCons "AnnotationUnsafe" PrefixI True) (S1 (MetaSel (Just "unAnnotation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

pattern Annotation :: Text -> Annotation tag Source #

pattern WithAnn :: Annotation tag -> Annotation tag Source #

class KnownAnnTag tag where Source #

type TypeAnn = Annotation TypeTag Source #

type FieldAnn = Annotation FieldTag Source #

type VarAnn = Annotation VarTag Source #

type SomeAnn = Annotation SomeTag Source #

ann :: HasCallStack => Text -> Annotation a Source #

Makes an Annotation from its textual value, prefix (%@:) excluded Throws an error if the given Text contains invalid characters

mkAnnotation :: Text -> Either Text (Annotation a) Source #

Makes an Annotation from its textual value, prefix (%@:) excluded Returns a Text error message if the given Text contains invalid characters

specialVarAnns :: [Text] Source #

List of all the special Variable Annotations, only allowed in CAR and CDR instructions, prefix (@) excluded. These do not respect the rules of isValidAnnStart and isValidAnnBodyChar.

specialFieldAnn :: Text Source #

The only special Field Annotation, only allowed in PAIR, LEFT and RIGHT instructions, prefix (%) excluded. This does not respect the rules of isValidAnnStart and isValidAnnBodyChar.

isValidAnnStart :: Char -> Bool Source #

Checks if a Char is valid to be the first of an annotation, prefix (%@:) excluded, the ones following should be checked with isValidAnnBodyChar instead. Note that this does not check Special Annotations, see specialVarAnns and specialFieldAnn

isValidAnnBodyChar :: Char -> Bool Source #

Checks if a Char is valid to be part of an annotation, following a valid first character (see isValidAnnStart) and the prefix (%@:). Note that this does not check Special Annotations, see specialVarAnns and specialFieldAnn

renderAnn :: forall tag. KnownAnnTag tag => Annotation tag -> Doc Source #

renderWEAnn :: forall tag. KnownAnnTag tag => Annotation tag -> Doc Source #

Prints empty prefix in case of noAnn.

Such functionality is required in case when instruction has two annotations of the same type, former is empty and the latter is not. So that `PAIR noAnn noAnn noAnn %kek` is printed as `PAIR % %kek`