plutus-core-1.34.1.0: Language library for Plutus Core
Safe HaskellSafe-Inferred
LanguageHaskell2010

PlutusCore.Annotation

Synopsis

Documentation

data Ann Source #

An annotation type used during the compilation.

Constructors

Ann 

Instances

Instances details
Generic Ann Source # 
Instance details

Defined in PlutusCore.Annotation

Associated Types

type Rep AnnTypeType Source #

Methods

fromAnnRep Ann x Source #

toRep Ann x → Ann Source #

Show Ann Source # 
Instance details

Defined in PlutusCore.Annotation

Methods

showsPrecIntAnnShowS Source #

showAnnString Source #

showList ∷ [Ann] → ShowS Source #

Eq Ann Source # 
Instance details

Defined in PlutusCore.Annotation

Methods

(==)AnnAnnBool Source #

(/=)AnnAnnBool Source #

Ord Ann Source # 
Instance details

Defined in PlutusCore.Annotation

Methods

compareAnnAnnOrdering Source #

(<)AnnAnnBool Source #

(<=)AnnAnnBool Source #

(>)AnnAnnBool Source #

(>=)AnnAnnBool Source #

maxAnnAnnAnn Source #

minAnnAnnAnn Source #

Hashable Ann Source # 
Instance details

Defined in PlutusCore.Annotation

Methods

hashWithSaltIntAnnInt Source #

hashAnnInt Source #

Pretty Ann Source # 
Instance details

Defined in PlutusCore.Annotation

Methods

prettyAnnDoc ann Source #

prettyList ∷ [Ann] → Doc ann Source #

type Rep Ann Source # 
Instance details

Defined in PlutusCore.Annotation

type Rep Ann = D1 ('MetaData "Ann" "PlutusCore.Annotation" "plutus-core-1.34.1.0-inplace" 'False) (C1 ('MetaCons "Ann" 'PrefixI 'True) (S1 ('MetaSel ('Just "annInline") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Inline) :*: S1 ('MetaSel ('Just "annSrcSpans") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SrcSpans)))

data SrcSpan Source #

The span between two source locations.

This corresponds roughly to the SrcSpan used by GHC, but we define our own version so we don't have to depend on ghc to use it.

The line and column numbers are 1-based, and the unit is Unicode code point (or Char).

Constructors

SrcSpan 

Fields

Instances

Instances details
Generic SrcSpan Source # 
Instance details

Defined in PlutusCore.Annotation

Associated Types

type Rep SrcSpanTypeType Source #

Methods

fromSrcSpanRep SrcSpan x Source #

toRep SrcSpan x → SrcSpan Source #

Show SrcSpan Source # 
Instance details

Defined in PlutusCore.Annotation

NFData SrcSpan Source # 
Instance details

Defined in PlutusCore.Annotation

Methods

rnfSrcSpan → () Source #

Flat SrcSpan Source # 
Instance details

Defined in PlutusCore.Annotation

Eq SrcSpan Source # 
Instance details

Defined in PlutusCore.Annotation

Methods

(==)SrcSpanSrcSpanBool Source #

(/=)SrcSpanSrcSpanBool Source #

Ord SrcSpan Source # 
Instance details

Defined in PlutusCore.Annotation

Hashable SrcSpan Source # 
Instance details

Defined in PlutusCore.Annotation

Methods

hashWithSaltIntSrcSpanInt Source #

hashSrcSpanInt Source #

Pretty SrcSpan Source # 
Instance details

Defined in PlutusCore.Annotation

Methods

prettySrcSpanDoc ann Source #

prettyList ∷ [SrcSpan] → Doc ann Source #

Exception (UniqueError SrcSpan) Source # 
Instance details

Defined in PlutusCore.Error

type Rep SrcSpan Source # 
Instance details

Defined in PlutusCore.Annotation

type Rep SrcSpan = D1 ('MetaData "SrcSpan" "PlutusCore.Annotation" "plutus-core-1.34.1.0-inplace" 'False) (C1 ('MetaCons "SrcSpan" 'PrefixI 'True) ((S1 ('MetaSel ('Just "srcSpanFile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath) :*: S1 ('MetaSel ('Just "srcSpanSLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "srcSpanSCol") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Just "srcSpanELine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "srcSpanECol") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))))

newtype SrcSpans Source #

Constructors

SrcSpans 

Fields

Instances

Instances details
Monoid SrcSpans Source # 
Instance details

Defined in PlutusCore.Annotation

Semigroup SrcSpans Source # 
Instance details

Defined in PlutusCore.Annotation

Generic SrcSpans Source # 
Instance details

Defined in PlutusCore.Annotation

Associated Types

type Rep SrcSpansTypeType Source #

Show SrcSpans Source # 
Instance details

Defined in PlutusCore.Annotation

NFData SrcSpans Source # 
Instance details

Defined in PlutusCore.Annotation

Methods

rnfSrcSpans → () Source #

Flat SrcSpans Source # 
Instance details

Defined in PlutusCore.Annotation

Eq SrcSpans Source # 
Instance details

Defined in PlutusCore.Annotation

Ord SrcSpans Source # 
Instance details

Defined in PlutusCore.Annotation

Hashable SrcSpans Source # 
Instance details

Defined in PlutusCore.Annotation

MonoFoldable SrcSpans Source # 
Instance details

Defined in PlutusCore.Annotation

Methods

ofoldMapMonoid m ⇒ (Element SrcSpans → m) → SrcSpans → m Source #

ofoldr ∷ (Element SrcSpans → b → b) → b → SrcSpans → b Source #

ofoldl' ∷ (a → Element SrcSpans → a) → a → SrcSpans → a Source #

otoListSrcSpans → [Element SrcSpans] Source #

oall ∷ (Element SrcSpansBool) → SrcSpansBool Source #

oany ∷ (Element SrcSpansBool) → SrcSpansBool Source #

onullSrcSpansBool Source #

olengthSrcSpansInt Source #

olength64SrcSpansInt64 Source #

ocompareLengthIntegral i ⇒ SrcSpans → i → Ordering Source #

otraverse_Applicative f ⇒ (Element SrcSpans → f b) → SrcSpans → f () Source #

ofor_Applicative f ⇒ SrcSpans → (Element SrcSpans → f b) → f () Source #

omapM_Applicative m ⇒ (Element SrcSpans → m ()) → SrcSpans → m () Source #

oforM_Applicative m ⇒ SrcSpans → (Element SrcSpans → m ()) → m () Source #

ofoldlMMonad m ⇒ (a → Element SrcSpans → m a) → a → SrcSpans → m a Source #

ofoldMap1ExSemigroup m ⇒ (Element SrcSpans → m) → SrcSpans → m Source #

ofoldr1Ex ∷ (Element SrcSpansElement SrcSpansElement SrcSpans) → SrcSpansElement SrcSpans Source #

ofoldl1Ex' ∷ (Element SrcSpansElement SrcSpansElement SrcSpans) → SrcSpansElement SrcSpans Source #

headExSrcSpansElement SrcSpans Source #

lastExSrcSpansElement SrcSpans Source #

unsafeHeadSrcSpansElement SrcSpans Source #

unsafeLastSrcSpansElement SrcSpans Source #

maximumByEx ∷ (Element SrcSpansElement SrcSpansOrdering) → SrcSpansElement SrcSpans Source #

minimumByEx ∷ (Element SrcSpansElement SrcSpansOrdering) → SrcSpansElement SrcSpans Source #

oelemElement SrcSpansSrcSpansBool Source #

onotElemElement SrcSpansSrcSpansBool Source #

Pretty SrcSpans Source # 
Instance details

Defined in PlutusCore.Annotation

Methods

prettySrcSpansDoc ann Source #

prettyList ∷ [SrcSpans] → Doc ann Source #

type Rep SrcSpans Source # 
Instance details

Defined in PlutusCore.Annotation

type Rep SrcSpans = D1 ('MetaData "SrcSpans" "PlutusCore.Annotation" "plutus-core-1.34.1.0-inplace" 'True) (C1 ('MetaCons "SrcSpans" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSrcSpans") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set SrcSpan))))
type Element SrcSpans Source # 
Instance details

Defined in PlutusCore.Annotation

newtype InlineHints name a Source #

Constructors

InlineHints 

Fields

Instances

Instances details
Monoid (InlineHints name a) Source # 
Instance details

Defined in PlutusCore.Annotation

Methods

memptyInlineHints name a Source #

mappendInlineHints name a → InlineHints name a → InlineHints name a Source #

mconcat ∷ [InlineHints name a] → InlineHints name a Source #

Semigroup (InlineHints name a) Source # 
Instance details

Defined in PlutusCore.Annotation

Methods

(<>)InlineHints name a → InlineHints name a → InlineHints name a Source #

sconcatNonEmpty (InlineHints name a) → InlineHints name a Source #

stimesIntegral b ⇒ b → InlineHints name a → InlineHints name a Source #

Show (InlineHints name a) Source # 
Instance details

Defined in PlutusCore.Annotation

Methods

showsPrecIntInlineHints name a → ShowS Source #

showInlineHints name a → String Source #

showList ∷ [InlineHints name a] → ShowS Source #

data Inline Source #

Constructors

AlwaysInline

When calling PlutusIR.Compiler.Definitions.defineTerm to add a new term definition, if we annotation the var on the LHS of the definition with AlwaysInline, the inliner will always inline that var.

This is currently used to ensure builtin functions such as trace (when the remove-trace flag is on and trace is rewritten to const) are inlined, because the inliner would otherwise not inline them. To achieve that, we annotate the definition with AlwaysInline when defining trace, i.e., trace AlwaysInline = _ a -> a.

MayInline 

Instances

Instances details
Generic Inline Source # 
Instance details

Defined in PlutusCore.Annotation

Associated Types

type Rep InlineTypeType Source #

Methods

fromInlineRep Inline x Source #

toRep Inline x → Inline Source #

Show Inline Source # 
Instance details

Defined in PlutusCore.Annotation

Eq Inline Source # 
Instance details

Defined in PlutusCore.Annotation

Methods

(==)InlineInlineBool Source #

(/=)InlineInlineBool Source #

Ord Inline Source # 
Instance details

Defined in PlutusCore.Annotation

Hashable Inline Source # 
Instance details

Defined in PlutusCore.Annotation

Methods

hashWithSaltIntInlineInt Source #

hashInlineInt Source #

type Rep Inline Source # 
Instance details

Defined in PlutusCore.Annotation

type Rep Inline = D1 ('MetaData "Inline" "PlutusCore.Annotation" "plutus-core-1.34.1.0-inplace" 'False) (C1 ('MetaCons "AlwaysInline" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "MayInline" 'PrefixI 'False) (U1TypeType))

annMayInlineAnn Source #

Create an Ann with MayInline.

data SourcePos Source #

The data type SourcePos represents source positions. It contains the name of the source file, a line number, and a column number. Source line and column positions change intensively during parsing, so we need to make them strict to avoid memory leaks.

Constructors

SourcePos 

Fields

Instances

Instances details
Data SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Methods

gfoldl ∷ (∀ d b. Data d ⇒ c (d → b) → d → c b) → (∀ g. g → c g) → SourcePos → c SourcePos Source #

gunfold ∷ (∀ b r. Data b ⇒ c (b → r) → c r) → (∀ r. r → c r) → Constr → c SourcePos Source #

toConstrSourcePosConstr Source #

dataTypeOfSourcePosDataType Source #

dataCast1Typeable t ⇒ (∀ d. Data d ⇒ c (t d)) → Maybe (c SourcePos) Source #

dataCast2Typeable t ⇒ (∀ d e. (Data d, Data e) ⇒ c (t d e)) → Maybe (c SourcePos) Source #

gmapT ∷ (∀ b. Data b ⇒ b → b) → SourcePosSourcePos Source #

gmapQl ∷ (r → r' → r) → r → (∀ d. Data d ⇒ d → r') → SourcePos → r Source #

gmapQr ∷ ∀ r r'. (r' → r → r) → r → (∀ d. Data d ⇒ d → r') → SourcePos → r Source #

gmapQ ∷ (∀ d. Data d ⇒ d → u) → SourcePos → [u] Source #

gmapQiInt → (∀ d. Data d ⇒ d → u) → SourcePos → u Source #

gmapMMonad m ⇒ (∀ d. Data d ⇒ d → m d) → SourcePos → m SourcePos Source #

gmapMpMonadPlus m ⇒ (∀ d. Data d ⇒ d → m d) → SourcePos → m SourcePos Source #

gmapMoMonadPlus m ⇒ (∀ d. Data d ⇒ d → m d) → SourcePos → m SourcePos Source #

Generic SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Associated Types

type Rep SourcePosTypeType Source #

Read SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Show SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

NFData SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Methods

rnfSourcePos → () Source #

Eq SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Ord SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Pretty SourcePos Source # 
Instance details

Defined in PlutusCore.Error

Methods

prettySourcePosDoc ann Source #

prettyList ∷ [SourcePos] → Doc ann Source #

type Rep SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

type Rep SourcePos = D1 ('MetaData "SourcePos" "Text.Megaparsec.Pos" "megaparsec-9.6.1-2lyGI2Uoag79kpXJQceOQM" 'False) (C1 ('MetaCons "SourcePos" 'PrefixI 'True) (S1 ('MetaSel ('Just "sourceName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath) :*: (S1 ('MetaSel ('Just "sourceLine") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Pos) :*: S1 ('MetaSel ('Just "sourceColumn") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Pos))))

data Pos Source #

Pos is the type for positive integers. This is used to represent line number, column number, and similar things like indentation level. Semigroup instance can be used to safely and efficiently add Poses together.

Since: megaparsec-5.0.0

Instances

Instances details
Data Pos 
Instance details

Defined in Text.Megaparsec.Pos

Methods

gfoldl ∷ (∀ d b. Data d ⇒ c (d → b) → d → c b) → (∀ g. g → c g) → Pos → c Pos Source #

gunfold ∷ (∀ b r. Data b ⇒ c (b → r) → c r) → (∀ r. r → c r) → Constr → c Pos Source #

toConstrPosConstr Source #

dataTypeOfPosDataType Source #

dataCast1Typeable t ⇒ (∀ d. Data d ⇒ c (t d)) → Maybe (c Pos) Source #

dataCast2Typeable t ⇒ (∀ d e. (Data d, Data e) ⇒ c (t d e)) → Maybe (c Pos) Source #

gmapT ∷ (∀ b. Data b ⇒ b → b) → PosPos Source #

gmapQl ∷ (r → r' → r) → r → (∀ d. Data d ⇒ d → r') → Pos → r Source #

gmapQr ∷ ∀ r r'. (r' → r → r) → r → (∀ d. Data d ⇒ d → r') → Pos → r Source #

gmapQ ∷ (∀ d. Data d ⇒ d → u) → Pos → [u] Source #

gmapQiInt → (∀ d. Data d ⇒ d → u) → Pos → u Source #

gmapMMonad m ⇒ (∀ d. Data d ⇒ d → m d) → Pos → m Pos Source #

gmapMpMonadPlus m ⇒ (∀ d. Data d ⇒ d → m d) → Pos → m Pos Source #

gmapMoMonadPlus m ⇒ (∀ d. Data d ⇒ d → m d) → Pos → m Pos Source #

Semigroup Pos 
Instance details

Defined in Text.Megaparsec.Pos

Methods

(<>)PosPosPos Source #

sconcatNonEmpty PosPos Source #

stimesIntegral b ⇒ b → PosPos Source #

Generic Pos 
Instance details

Defined in Text.Megaparsec.Pos

Associated Types

type Rep PosTypeType Source #

Methods

fromPosRep Pos x Source #

toRep Pos x → Pos Source #

Read Pos 
Instance details

Defined in Text.Megaparsec.Pos

Show Pos 
Instance details

Defined in Text.Megaparsec.Pos

Methods

showsPrecIntPosShowS Source #

showPosString Source #

showList ∷ [Pos] → ShowS Source #

NFData Pos 
Instance details

Defined in Text.Megaparsec.Pos

Methods

rnfPos → () Source #

Eq Pos 
Instance details

Defined in Text.Megaparsec.Pos

Methods

(==)PosPosBool Source #

(/=)PosPosBool Source #

Ord Pos 
Instance details

Defined in Text.Megaparsec.Pos

Methods

comparePosPosOrdering Source #

(<)PosPosBool Source #

(<=)PosPosBool Source #

(>)PosPosBool Source #

(>=)PosPosBool Source #

maxPosPosPos Source #

minPosPosPos Source #

type Rep Pos 
Instance details

Defined in Text.Megaparsec.Pos

type Rep Pos = D1 ('MetaData "Pos" "Text.Megaparsec.Pos" "megaparsec-9.6.1-2lyGI2Uoag79kpXJQceOQM" 'True) (C1 ('MetaCons "Pos" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

addSrcSpanSrcSpanAnnAnn Source #

Add an extra SrcSpan to existing SrcSpans of Ann

lineInSrcSpanPosSrcSpanBool Source #

Tells if a line (positive integer) falls inside a SrcSpan.