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

PlutusIR.Error

Documentation

data Error uni fun a Source #

Constructors

CompilationError !a !Text

A generic compilation error.

UnsupportedError !a !Text

An error relating specifically to an unsupported feature.

OptionsError !Text

An error relating to compilation options.

PLCError !(Error uni fun a)

An error from running some PLC function, lifted into this error type for convenience.

PLCTypeError !(TypeError (Term TyName Name uni fun ()) uni fun a) 
PIRTypeError !(TypeErrorExt uni a) 

Instances

Instances details
(PrettyUni uni, Pretty fun, Pretty ann) ⇒ PrettyBy PrettyConfigPlc (Error uni fun ann) Source # 
Instance details

Defined in PlutusIR.Error

Methods

prettyByPrettyConfigPlcError uni fun ann → Doc ann0 Source #

prettyListByPrettyConfigPlc → [Error uni fun ann] → Doc ann0 Source #

Functor (Error uni fun) Source # 
Instance details

Defined in PlutusIR.Error

Methods

fmap ∷ (a → b) → Error uni fun a → Error uni fun b Source #

(<$) ∷ a → Error uni fun b → Error uni fun a Source #

(ThrowableBuiltins uni fun, Pretty ann, Typeable ann) ⇒ Exception (Error uni fun ann) Source # 
Instance details

Defined in PlutusIR.Error

Methods

toExceptionError uni fun ann → SomeException Source #

fromExceptionSomeExceptionMaybe (Error uni fun ann) Source #

displayExceptionError uni fun ann → String Source #

(PrettyUni uni, Pretty fun, Pretty ann) ⇒ Show (Error uni fun ann) Source # 
Instance details

Defined in PlutusIR.Error

Methods

showsPrecIntError uni fun ann → ShowS Source #

showError uni fun ann → String Source #

showList ∷ [Error uni fun ann] → ShowS Source #

AsFreeVariableError (Error uni fun a) Source # 
Instance details

Defined in PlutusIR.Error

Methods

_FreeVariableError ∷ Prism' (Error uni fun a) FreeVariableError Source #

_FreeUnique ∷ Prism' (Error uni fun a) Unique Source #

_FreeIndex ∷ Prism' (Error uni fun a) Index Source #

AsParserErrorBundle (Error uni fun a) Source # 
Instance details

Defined in PlutusIR.Error

(PrettyUni uni, Pretty fun, Pretty ann) ⇒ Pretty (Error uni fun ann) Source # 
Instance details

Defined in PlutusIR.Error

Methods

prettyError uni fun ann → Doc ann0 Source #

prettyList ∷ [Error uni fun ann] → Doc ann0 Source #

AsUniqueError (Error uni fun a) a Source # 
Instance details

Defined in PlutusIR.Error

Methods

_UniqueError ∷ Prism' (Error uni fun a) (UniqueError a) Source #

_MultiplyDefined ∷ Prism' (Error uni fun a) (Unique, a, a) Source #

_IncoherentUsage ∷ Prism' (Error uni fun a) (Unique, a, a) Source #

_FreeVariable ∷ Prism' (Error uni fun a) (Unique, a) Source #

AsTypeErrorExt (Error uni fun a) uni a Source # 
Instance details

Defined in PlutusIR.Error

Methods

_TypeErrorExt ∷ Prism' (Error uni fun a) (TypeErrorExt uni a) Source #

_MalformedDataConstrResType ∷ Prism' (Error uni fun a) (a, Type TyName uni a) Source #

AsError (Error uni fun a) uni fun a Source # 
Instance details

Defined in PlutusIR.Error

Methods

_Error ∷ Prism' (Error uni fun a) (Error uni fun a) Source #

_CompilationError ∷ Prism' (Error uni fun a) (a, Text) Source #

_UnsupportedError ∷ Prism' (Error uni fun a) (a, Text) Source #

_OptionsError ∷ Prism' (Error uni fun a) Text Source #

_PLCError ∷ Prism' (Error uni fun a) (Error0 uni fun a) Source #

_PLCTypeError ∷ Prism' (Error uni fun a) (TypeError (Term TyName Name uni fun ()) uni fun a) Source #

_PIRTypeError ∷ Prism' (Error uni fun a) (TypeErrorExt uni a) Source #

AsTypeError (Error uni fun a) (Term TyName Name uni fun ()) uni fun a Source # 
Instance details

Defined in PlutusIR.Error

Methods

_TypeError ∷ Prism' (Error uni fun a) (TypeError (Term TyName Name uni fun ()) uni fun a) Source #

_KindMismatch ∷ Prism' (Error uni fun a) (a, Type TyName uni (), ExpectedShapeOr (Kind ()), Kind ()) Source #

_TypeMismatch ∷ Prism' (Error uni fun a) (a, Term TyName Name uni fun (), ExpectedShapeOr (Type TyName uni ()), Normalized (Type TyName uni ())) Source #

_TyNameMismatch ∷ Prism' (Error uni fun a) (a, TyName, TyName) Source #

_NameMismatch ∷ Prism' (Error uni fun a) (a, Name, Name) Source #

_FreeTypeVariableE ∷ Prism' (Error uni fun a) (a, TyName) Source #

_FreeVariableE ∷ Prism' (Error uni fun a) (a, Name) Source #

_UnknownBuiltinFunctionE ∷ Prism' (Error uni fun a) (a, fun) Source #

class AsTypeError r term (uni ∷ TypeType) fun ann | r → term uni fun ann where Source #

Minimal complete definition

_TypeError

Methods

_TypeError ∷ Prism' r (TypeError term uni fun ann) Source #

_KindMismatch ∷ Prism' r (ann, Type TyName uni (), ExpectedShapeOr (Kind ()), Kind ()) Source #

_TypeMismatch ∷ Prism' r (ann, term, ExpectedShapeOr (Type TyName uni ()), Normalized (Type TyName uni ())) Source #

_TyNameMismatch ∷ Prism' r (ann, TyName, TyName) Source #

_NameMismatch ∷ Prism' r (ann, Name, Name) Source #

_FreeTypeVariableE ∷ Prism' r (ann, TyName) Source #

_FreeVariableE ∷ Prism' r (ann, Name) Source #

_UnknownBuiltinFunctionE ∷ Prism' r (ann, fun) Source #

Instances

Instances details
AsTypeError (Error uni fun ann) (Term TyName Name uni fun ()) uni fun ann 
Instance details

Defined in PlutusCore.Error

Methods

_TypeError ∷ Prism' (Error uni fun ann) (TypeError (Term TyName Name uni fun ()) uni fun ann) Source #

_KindMismatch ∷ Prism' (Error uni fun ann) (ann, Type TyName uni (), ExpectedShapeOr (Kind ()), Kind ()) Source #

_TypeMismatch ∷ Prism' (Error uni fun ann) (ann, Term TyName Name uni fun (), ExpectedShapeOr (Type TyName uni ()), Normalized (Type TyName uni ())) Source #

_TyNameMismatch ∷ Prism' (Error uni fun ann) (ann, TyName, TyName) Source #

_NameMismatch ∷ Prism' (Error uni fun ann) (ann, Name, Name) Source #

_FreeTypeVariableE ∷ Prism' (Error uni fun ann) (ann, TyName) Source #

_FreeVariableE ∷ Prism' (Error uni fun ann) (ann, Name) Source #

_UnknownBuiltinFunctionE ∷ Prism' (Error uni fun ann) (ann, fun) Source #

AsTypeError (Error uni fun ann) (Term TyName Name uni fun ()) uni fun ann Source # 
Instance details

Defined in PlutusIR.Compiler.Error

Methods

_TypeError ∷ Prism' (Error uni fun ann) (TypeError (Term TyName Name uni fun ()) uni fun ann) Source #

_KindMismatch ∷ Prism' (Error uni fun ann) (ann, Type TyName uni (), ExpectedShapeOr (Kind ()), Kind ()) Source #

_TypeMismatch ∷ Prism' (Error uni fun ann) (ann, Term TyName Name uni fun (), ExpectedShapeOr (Type TyName uni ()), Normalized (Type TyName uni ())) Source #

_TyNameMismatch ∷ Prism' (Error uni fun ann) (ann, TyName, TyName) Source #

_NameMismatch ∷ Prism' (Error uni fun ann) (ann, Name, Name) Source #

_FreeTypeVariableE ∷ Prism' (Error uni fun ann) (ann, TyName) Source #

_FreeVariableE ∷ Prism' (Error uni fun ann) (ann, Name) Source #

_UnknownBuiltinFunctionE ∷ Prism' (Error uni fun ann) (ann, fun) Source #

AsTypeError (Error uni fun a) (Term TyName Name uni fun ()) uni fun a Source # 
Instance details

Defined in PlutusIR.Error

Methods

_TypeError ∷ Prism' (Error uni fun a) (TypeError (Term TyName Name uni fun ()) uni fun a) Source #

_KindMismatch ∷ Prism' (Error uni fun a) (a, Type TyName uni (), ExpectedShapeOr (Kind ()), Kind ()) Source #

_TypeMismatch ∷ Prism' (Error uni fun a) (a, Term TyName Name uni fun (), ExpectedShapeOr (Type TyName uni ()), Normalized (Type TyName uni ())) Source #

_TyNameMismatch ∷ Prism' (Error uni fun a) (a, TyName, TyName) Source #

_NameMismatch ∷ Prism' (Error uni fun a) (a, Name, Name) Source #

_FreeTypeVariableE ∷ Prism' (Error uni fun a) (a, TyName) Source #

_FreeVariableE ∷ Prism' (Error uni fun a) (a, Name) Source #

_UnknownBuiltinFunctionE ∷ Prism' (Error uni fun a) (a, fun) Source #

AsTypeError (TypeError term uni fun ann) term uni fun ann 
Instance details

Defined in PlutusCore.Error

Methods

_TypeError ∷ Prism' (TypeError term uni fun ann) (TypeError term uni fun ann) Source #

_KindMismatch ∷ Prism' (TypeError term uni fun ann) (ann, Type TyName uni (), ExpectedShapeOr (Kind ()), Kind ()) Source #

_TypeMismatch ∷ Prism' (TypeError term uni fun ann) (ann, term, ExpectedShapeOr (Type TyName uni ()), Normalized (Type TyName uni ())) Source #

_TyNameMismatch ∷ Prism' (TypeError term uni fun ann) (ann, TyName, TyName) Source #

_NameMismatch ∷ Prism' (TypeError term uni fun ann) (ann, Name, Name) Source #

_FreeTypeVariableE ∷ Prism' (TypeError term uni fun ann) (ann, TyName) Source #

_FreeVariableE ∷ Prism' (TypeError term uni fun ann) (ann, Name) Source #

_UnknownBuiltinFunctionE ∷ Prism' (TypeError term uni fun ann) (ann, fun) Source #

data TypeError term (uni ∷ TypeType) fun ann Source #

Instances

Instances details
(Pretty term, PrettyUni uni, Pretty fun, Pretty ann) ⇒ PrettyBy PrettyConfigPlc (TypeError term uni fun ann) 
Instance details

Defined in PlutusCore.Error

Methods

prettyByPrettyConfigPlcTypeError term uni fun ann → Doc ann0 Source #

prettyListByPrettyConfigPlc → [TypeError term uni fun ann] → Doc ann0 Source #

Functor (TypeError term uni fun) 
Instance details

Defined in PlutusCore.Error

Methods

fmap ∷ (a → b) → TypeError term uni fun a → TypeError term uni fun b Source #

(<$) ∷ a → TypeError term uni fun b → TypeError term uni fun a Source #

Generic (TypeError term uni fun ann) 
Instance details

Defined in PlutusCore.Error

Associated Types

type Rep (TypeError term uni fun ann) ∷ TypeType Source #

Methods

fromTypeError term uni fun ann → Rep (TypeError term uni fun ann) x Source #

toRep (TypeError term uni fun ann) x → TypeError term uni fun ann Source #

(GShow uni, Show term, Show ann, Show fun) ⇒ Show (TypeError term uni fun ann) 
Instance details

Defined in PlutusCore.Error

Methods

showsPrecIntTypeError term uni fun ann → ShowS Source #

showTypeError term uni fun ann → String Source #

showList ∷ [TypeError term uni fun ann] → ShowS Source #

(Closed uni, NFData ann, NFData term, NFData fun) ⇒ NFData (TypeError term uni fun ann) 
Instance details

Defined in PlutusCore.Error

Methods

rnfTypeError term uni fun ann → () Source #

(GEq uni, Eq term, Eq ann, Eq fun) ⇒ Eq (TypeError term uni fun ann) 
Instance details

Defined in PlutusCore.Error

Methods

(==)TypeError term uni fun ann → TypeError term uni fun ann → Bool Source #

(/=)TypeError term uni fun ann → TypeError term uni fun ann → Bool Source #

AsTypeError (TypeError term uni fun ann) term uni fun ann 
Instance details

Defined in PlutusCore.Error

Methods

_TypeError ∷ Prism' (TypeError term uni fun ann) (TypeError term uni fun ann) Source #

_KindMismatch ∷ Prism' (TypeError term uni fun ann) (ann, Type TyName uni (), ExpectedShapeOr (Kind ()), Kind ()) Source #

_TypeMismatch ∷ Prism' (TypeError term uni fun ann) (ann, term, ExpectedShapeOr (Type TyName uni ()), Normalized (Type TyName uni ())) Source #

_TyNameMismatch ∷ Prism' (TypeError term uni fun ann) (ann, TyName, TyName) Source #

_NameMismatch ∷ Prism' (TypeError term uni fun ann) (ann, Name, Name) Source #

_FreeTypeVariableE ∷ Prism' (TypeError term uni fun ann) (ann, TyName) Source #

_FreeVariableE ∷ Prism' (TypeError term uni fun ann) (ann, Name) Source #

_UnknownBuiltinFunctionE ∷ Prism' (TypeError term uni fun ann) (ann, fun) Source #

type Rep (TypeError term uni fun ann) 
Instance details

Defined in PlutusCore.Error

type Rep (TypeError term uni fun ann) = D1 ('MetaData "TypeError" "PlutusCore.Error" "plutus-core-1.34.1.0-inplace" 'False) ((C1 ('MetaCons "KindMismatch" 'PrefixI 'False) ((S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ann) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Type TyName uni ()))) :*: (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ExpectedShapeOr (Kind ()))) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Kind ())))) :+: (C1 ('MetaCons "TypeMismatch" 'PrefixI 'False) ((S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ann) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 term)) :*: (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ExpectedShapeOr (Type TyName uni ()))) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Normalized (Type TyName uni ()))))) :+: C1 ('MetaCons "TyNameMismatch" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ann) :*: (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TyName) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TyName))))) :+: ((C1 ('MetaCons "NameMismatch" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ann) :*: (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Name) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Name))) :+: C1 ('MetaCons "FreeTypeVariableE" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ann) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TyName))) :+: (C1 ('MetaCons "FreeVariableE" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ann) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Name)) :+: C1 ('MetaCons "UnknownBuiltinFunctionE" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ann) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 fun)))))

class AsTypeErrorExt r uni ann | r → uni ann where Source #

Minimal complete definition

_TypeErrorExt

Methods

_TypeErrorExt ∷ Prism' r (TypeErrorExt uni ann) Source #

_MalformedDataConstrResType ∷ Prism' r (ann, Type TyName uni ann) Source #

Instances

Instances details
AsTypeErrorExt (TypeErrorExt uni ann) uni ann Source # 
Instance details

Defined in PlutusIR.Error

Methods

_TypeErrorExt ∷ Prism' (TypeErrorExt uni ann) (TypeErrorExt uni ann) Source #

_MalformedDataConstrResType ∷ Prism' (TypeErrorExt uni ann) (ann, Type TyName uni ann) Source #

AsTypeErrorExt (Error uni fun a) uni a Source # 
Instance details

Defined in PlutusIR.Error

Methods

_TypeErrorExt ∷ Prism' (Error uni fun a) (TypeErrorExt uni a) Source #

_MalformedDataConstrResType ∷ Prism' (Error uni fun a) (a, Type TyName uni a) Source #

class AsError r uni fun a | r → uni fun a where Source #

Minimal complete definition

_Error

Methods

_Error ∷ Prism' r (Error uni fun a) Source #

_CompilationError ∷ Prism' r (a, Text) Source #

_UnsupportedError ∷ Prism' r (a, Text) Source #

_OptionsError ∷ Prism' r Text Source #

_PLCError ∷ Prism' r (Error uni fun a) Source #

_PLCTypeError ∷ Prism' r (TypeError (Term TyName Name uni fun ()) uni fun a) Source #

_PIRTypeError ∷ Prism' r (TypeErrorExt uni a) Source #

Instances

Instances details
AsError (Error uni fun a) uni fun a Source # 
Instance details

Defined in PlutusIR.Error

Methods

_Error ∷ Prism' (Error uni fun a) (Error uni fun a) Source #

_CompilationError ∷ Prism' (Error uni fun a) (a, Text) Source #

_UnsupportedError ∷ Prism' (Error uni fun a) (a, Text) Source #

_OptionsError ∷ Prism' (Error uni fun a) Text Source #

_PLCError ∷ Prism' (Error uni fun a) (Error0 uni fun a) Source #

_PLCTypeError ∷ Prism' (Error uni fun a) (TypeError (Term TyName Name uni fun ()) uni fun a) Source #

_PIRTypeError ∷ Prism' (Error uni fun a) (TypeErrorExt uni a) Source #

data TypeErrorExt uni ann Source #

Constructors

MalformedDataConstrResType !ann !(Type TyName uni ann) 

Instances

Instances details
(PrettyUni uni, Pretty ann) ⇒ PrettyBy PrettyConfigPlc (TypeErrorExt uni ann) Source # 
Instance details

Defined in PlutusIR.Error

Methods

prettyByPrettyConfigPlcTypeErrorExt uni ann → Doc ann0 Source #

prettyListByPrettyConfigPlc → [TypeErrorExt uni ann] → Doc ann0 Source #

Functor (TypeErrorExt uni) Source # 
Instance details

Defined in PlutusIR.Error

Methods

fmap ∷ (a → b) → TypeErrorExt uni a → TypeErrorExt uni b Source #

(<$) ∷ a → TypeErrorExt uni b → TypeErrorExt uni a Source #

Generic (TypeErrorExt uni ann) Source # 
Instance details

Defined in PlutusIR.Error

Associated Types

type Rep (TypeErrorExt uni ann) ∷ TypeType Source #

Methods

fromTypeErrorExt uni ann → Rep (TypeErrorExt uni ann) x Source #

toRep (TypeErrorExt uni ann) x → TypeErrorExt uni ann Source #

(Show ann, GShow uni) ⇒ Show (TypeErrorExt uni ann) Source # 
Instance details

Defined in PlutusIR.Error

Methods

showsPrecIntTypeErrorExt uni ann → ShowS Source #

showTypeErrorExt uni ann → String Source #

showList ∷ [TypeErrorExt uni ann] → ShowS Source #

(NFData ann, Closed uni) ⇒ NFData (TypeErrorExt uni ann) Source # 
Instance details

Defined in PlutusIR.Error

Methods

rnfTypeErrorExt uni ann → () Source #

(Eq ann, GEq uni) ⇒ Eq (TypeErrorExt uni ann) Source # 
Instance details

Defined in PlutusIR.Error

Methods

(==)TypeErrorExt uni ann → TypeErrorExt uni ann → Bool Source #

(/=)TypeErrorExt uni ann → TypeErrorExt uni ann → Bool Source #

AsTypeErrorExt (TypeErrorExt uni ann) uni ann Source # 
Instance details

Defined in PlutusIR.Error

Methods

_TypeErrorExt ∷ Prism' (TypeErrorExt uni ann) (TypeErrorExt uni ann) Source #

_MalformedDataConstrResType ∷ Prism' (TypeErrorExt uni ann) (ann, Type TyName uni ann) Source #

type Rep (TypeErrorExt uni ann) Source # 
Instance details

Defined in PlutusIR.Error

type Rep (TypeErrorExt uni ann) = D1 ('MetaData "TypeErrorExt" "PlutusIR.Error" "plutus-core-1.34.1.0-inplace-plutus-ir" 'False) (C1 ('MetaCons "MalformedDataConstrResType" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ann) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Type TyName uni ann))))

newtype Normalized a Source #

Constructors

Normalized 

Fields

Instances

Instances details
Foldable Normalized 
Instance details

Defined in PlutusCore.Core.Type

Methods

foldMonoid m ⇒ Normalized m → m Source #

foldMapMonoid m ⇒ (a → m) → Normalized a → m Source #

foldMap'Monoid m ⇒ (a → m) → Normalized a → m Source #

foldr ∷ (a → b → b) → b → Normalized a → b Source #

foldr' ∷ (a → b → b) → b → Normalized a → b Source #

foldl ∷ (b → a → b) → b → Normalized a → b Source #

foldl' ∷ (b → a → b) → b → Normalized a → b Source #

foldr1 ∷ (a → a → a) → Normalized a → a Source #

foldl1 ∷ (a → a → a) → Normalized a → a Source #

toListNormalized a → [a] Source #

nullNormalized a → Bool Source #

lengthNormalized a → Int Source #

elemEq a ⇒ a → Normalized a → Bool Source #

maximumOrd a ⇒ Normalized a → a Source #

minimumOrd a ⇒ Normalized a → a Source #

sumNum a ⇒ Normalized a → a Source #

productNum a ⇒ Normalized a → a Source #

Traversable Normalized 
Instance details

Defined in PlutusCore.Core.Type

Methods

traverseApplicative f ⇒ (a → f b) → Normalized a → f (Normalized b) Source #

sequenceAApplicative f ⇒ Normalized (f a) → f (Normalized a) Source #

mapMMonad m ⇒ (a → m b) → Normalized a → m (Normalized b) Source #

sequenceMonad m ⇒ Normalized (m a) → m (Normalized a) Source #

Applicative Normalized 
Instance details

Defined in PlutusCore.Core.Type

Methods

pure ∷ a → Normalized a Source #

(<*>)Normalized (a → b) → Normalized a → Normalized b Source #

liftA2 ∷ (a → b → c) → Normalized a → Normalized b → Normalized c Source #

(*>)Normalized a → Normalized b → Normalized b Source #

(<*)Normalized a → Normalized b → Normalized a Source #

Functor Normalized 
Instance details

Defined in PlutusCore.Core.Type

Methods

fmap ∷ (a → b) → Normalized a → Normalized b Source #

(<$) ∷ a → Normalized b → Normalized a Source #

PrettyBy config a ⇒ PrettyBy config (Normalized a) 
Instance details

Defined in PlutusCore.Core.Type

Methods

prettyBy ∷ config → Normalized a → Doc ann Source #

prettyListBy ∷ config → [Normalized a] → Doc ann Source #

Generic (Normalized a) 
Instance details

Defined in PlutusCore.Core.Type

Associated Types

type Rep (Normalized a) ∷ TypeType Source #

Methods

fromNormalized a → Rep (Normalized a) x Source #

toRep (Normalized a) x → Normalized a Source #

Show a ⇒ Show (Normalized a) 
Instance details

Defined in PlutusCore.Core.Type

NFData a ⇒ NFData (Normalized a) 
Instance details

Defined in PlutusCore.Core.Type

Methods

rnfNormalized a → () Source #

Eq a ⇒ Eq (Normalized a) 
Instance details

Defined in PlutusCore.Core.Type

Methods

(==)Normalized a → Normalized a → Bool Source #

(/=)Normalized a → Normalized a → Bool Source #

Rename a ⇒ Rename (Normalized a) 
Instance details

Defined in PlutusCore.Rename

Methods

renameMonadQuote m ⇒ Normalized a → m (Normalized a) Source #

Pretty a ⇒ Pretty (Normalized a) 
Instance details

Defined in PlutusCore.Core.Type

Methods

prettyNormalized a → Doc ann Source #

prettyList ∷ [Normalized a] → Doc ann Source #

type Rep (Normalized a) 
Instance details

Defined in PlutusCore.Core.Type

type Rep (Normalized a) = D1 ('MetaData "Normalized" "PlutusCore.Core.Type" "plutus-core-1.34.1.0-inplace" 'True) (C1 ('MetaCons "Normalized" 'PrefixI 'True) (S1 ('MetaSel ('Just "unNormalized") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))