morley-0.3.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 #

Constructors

Annotation Text 
Instances
Semigroup VarAnn Source # 
Instance details

Defined in Michelson.Untyped.Annotation

Monoid VarAnn Source # 
Instance details

Defined in Michelson.Untyped.Annotation

Arbitrary VarAnn Source # 
Instance details

Defined in Util.Test.Arbitrary

Arbitrary FieldAnn Source # 
Instance details

Defined in Util.Test.Arbitrary

Arbitrary TypeAnn Source # 
Instance details

Defined in Util.Test.Arbitrary

Buildable VarAnn Source # 
Instance details

Defined in Michelson.Untyped.Annotation

Methods

build :: VarAnn -> Builder #

Buildable FieldAnn Source # 
Instance details

Defined in Michelson.Untyped.Annotation

Methods

build :: FieldAnn -> Builder #

Buildable TypeAnn Source # 
Instance details

Defined in Michelson.Untyped.Annotation

Methods

build :: TypeAnn -> Builder #

ToADTArbitrary VarAnn Source # 
Instance details

Defined in Util.Test.Arbitrary

ToADTArbitrary FieldAnn Source # 
Instance details

Defined in Util.Test.Arbitrary

ToADTArbitrary TypeAnn Source # 
Instance details

Defined in Util.Test.Arbitrary

RenderDoc VarAnn Source # 
Instance details

Defined in Michelson.Untyped.Annotation

RenderDoc FieldAnn Source # 
Instance details

Defined in Michelson.Untyped.Annotation

RenderDoc TypeAnn Source # 
Instance details

Defined in Michelson.Untyped.Annotation

RenderAnn VarAnn Source # 
Instance details

Defined in Michelson.Untyped.Annotation

Methods

renderAnn :: VarAnn -> Doc Source #

RenderAnn FieldAnn Source # 
Instance details

Defined in Michelson.Untyped.Annotation

RenderAnn TypeAnn 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) #

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 #

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 #

type Rep (Annotation tag) Source # 
Instance details

Defined in Michelson.Untyped.Annotation

type Rep (Annotation tag) = D1 (MetaData "Annotation" "Michelson.Untyped.Annotation" "morley-0.3.0-7oMtJCcnhvo7MqJS85kloi" True) (C1 (MetaCons "Annotation" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

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

type TypeAnn = Annotation TypeTag Source #

type FieldAnn = Annotation FieldTag Source #

type VarAnn = Annotation VarTag Source #

class RenderAnn t where Source #

Typeclass for printing annotations, renderAnn 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`

Methods

renderAnn :: t -> Doc Source #

Instances
RenderAnn VarAnn Source # 
Instance details

Defined in Michelson.Untyped.Annotation

Methods

renderAnn :: VarAnn -> Doc Source #

RenderAnn FieldAnn Source # 
Instance details

Defined in Michelson.Untyped.Annotation

RenderAnn TypeAnn Source # 
Instance details

Defined in Michelson.Untyped.Annotation