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

PlutusPrelude

Synopsis

Reexports from base

(&) ∷ a → (a → b) → b infixl 1 Source #

& is a reverse application operator. This provides notational convenience. Its precedence is one higher than that of the forward application operator $, which allows & to be nested in $.

>>> 5 & (+1) & show
"6"

Since: base-4.8.0.0

(&&&)Arrow a ⇒ a b c → a b c' → a b (c, c') infixr 3 Source #

Fanout: send the input to both argument arrows and combine their output.

The default definition may be overridden with a more efficient version if desired.

(>>>) ∷ ∀ {k} cat (a ∷ k) (b ∷ k) (c ∷ k). Category cat ⇒ cat a b → cat b c → cat a c infixr 1 Source #

Left-to-right composition

(<&>)Functor f ⇒ f a → (a → b) → f b infixl 1 Source #

Flipped version of <$>.

(<&>) = flip fmap

Examples

Expand

Apply (+1) to a list, a Just and a Right:

>>> Just 2 <&> (+1)
Just 3
>>> [1,2,3] <&> (+1)
[2,3,4]
>>> Right 3 <&> (+1)
Right 4

Since: base-4.11.0.0

toListFoldable t ⇒ t a → [a] Source #

List of elements of a structure, from left to right. If the entire list is intended to be reduced via a fold, just fold the structure directly bypassing the list.

Examples

Expand

Basic usage:

>>> toList Nothing
[]
>>> toList (Just 42)
[42]
>>> toList (Left "foo")
[]
>>> toList (Node (Leaf 5) 17 (Node Empty 12 (Leaf 8)))
[5,17,12,8]

For lists, toList is the identity:

>>> toList [1, 2, 3]
[1,2,3]

Since: base-4.8.0.0

firstBifunctor p ⇒ (a → b) → p a c → p b c Source #

Map covariantly over the first argument.

first f ≡ bimap f id

Examples

Expand
>>> first toUpper ('j', 3)
('J',3)
>>> first toUpper (Left 'j')
Left 'J'

secondBifunctor p ⇒ (b → c) → p a b → p a c Source #

Map covariantly over the second argument.

secondbimap id

Examples

Expand
>>> second (+1) ('j', 3)
('j',4)
>>> second (+1) (Right 3)
Right 4

on ∷ (b → b → c) → (a → b) → a → a → c infixl 0 Source #

on b u x y runs the binary function b on the results of applying unary function u to two arguments x and y. From the opposite perspective, it transforms two inputs and combines the outputs.

((+) `on` f) x y = f x + f y

Typical usage: sortBy (compare `on` fst).

Algebraic properties:

  • (*) `on` id = (*) -- (if (*) ∉ {⊥, const ⊥})
  • ((*) `on` f) `on` g = (*) `on` (f . g)
  • flip on f . flip on g = flip on (g . f)

isNothingMaybe a → Bool Source #

The isNothing function returns True iff its argument is Nothing.

Examples

Expand

Basic usage:

>>> isNothing (Just 3)
False
>>> isNothing (Just ())
False
>>> isNothing Nothing
True

Only the outer constructor is taken into consideration:

>>> isNothing (Just Nothing)
False

isJustMaybe a → Bool Source #

The isJust function returns True iff its argument is of the form Just _.

Examples

Expand

Basic usage:

>>> isJust (Just 3)
True
>>> isJust (Just ())
True
>>> isJust Nothing
False

Only the outer constructor is taken into consideration:

>>> isJust (Just Nothing)
True

fromMaybe ∷ a → Maybe a → a Source #

The fromMaybe function takes a default value and a Maybe value. If the Maybe is Nothing, it returns the default value; otherwise, it returns the value contained in the Maybe.

Examples

Expand

Basic usage:

>>> fromMaybe "" (Just "Hello, World!")
"Hello, World!"
>>> fromMaybe "" Nothing
""

Read an integer from a string using readMaybe. If we fail to parse an integer, we want to return 0 by default:

>>> import Text.Read ( readMaybe )
>>> fromMaybe 0 (readMaybe "5")
5
>>> fromMaybe 0 (readMaybe "")
0

guardAlternative f ⇒ Bool → f () Source #

Conditional failure of Alternative computations. Defined by

guard True  = pure ()
guard False = empty

Examples

Expand

Common uses of guard include conditionally signaling an error in an error monad and conditionally rejecting the current choice in an Alternative-based parser.

As an example of signaling an error in the error monad Maybe, consider a safe division function safeDiv x y that returns Nothing when the denominator y is zero and Just (x `div` y) otherwise. For example:

>>> safeDiv 4 0
Nothing
>>> safeDiv 4 2
Just 2

A definition of safeDiv using guards, but not guard:

safeDiv :: Int -> Int -> Maybe Int
safeDiv x y | y /= 0    = Just (x `div` y)
            | otherwise = Nothing

A definition of safeDiv using guard and Monad do-notation:

safeDiv :: Int -> Int -> Maybe Int
safeDiv x y = do
  guard (y /= 0)
  return (x `div` y)

foldl'Foldable t ⇒ (b → a → b) → b → t a → b Source #

Left-associative fold of a structure but with strict application of the operator.

This ensures that each step of the fold is forced to Weak Head Normal Form before being applied, avoiding the collection of thunks that would otherwise occur. This is often what you want to strictly reduce a finite structure to a single strict result (e.g. sum).

For a general Foldable structure this should be semantically identical to,

foldl' f z = foldl' f z . toList

Since: base-4.6.0.0

for_ ∷ (Foldable t, Applicative f) ⇒ t a → (a → f b) → f () Source #

for_ is traverse_ with its arguments flipped. For a version that doesn't ignore the results see for. This is forM_ generalised to Applicative actions.

for_ is just like forM_, but generalised to Applicative actions.

Examples

Expand

Basic usage:

>>> for_ [1..4] print
1
2
3
4

traverse_ ∷ (Foldable t, Applicative f) ⇒ (a → f b) → t a → f () Source #

Map each element of a structure to an Applicative action, evaluate these actions from left to right, and ignore the results. For a version that doesn't ignore the results see traverse.

traverse_ is just like mapM_, but generalised to Applicative actions.

Examples

Expand

Basic usage:

>>> traverse_ print ["Hello", "world", "!"]
"Hello"
"world"
"!"

fold ∷ (Foldable t, Monoid m) ⇒ t m → m Source #

Given a structure with elements whose type is a Monoid, combine them via the monoid's (<>) operator. This fold is right-associative and lazy in the accumulator. When you need a strict left-associative fold, use foldMap' instead, with id as the map.

Examples

Expand

Basic usage:

>>> fold [[1, 2, 3], [4, 5], [6], []]
[1,2,3,4,5,6]
>>> fold $ Node (Leaf (Sum 1)) (Sum 3) (Leaf (Sum 5))
Sum {getSum = 9}

Folds of unbounded structures do not terminate when the monoid's (<>) operator is strict:

>>> fold (repeat Nothing)
* Hangs forever *

Lazy corecursive folds of unbounded structures are fine:

>>> take 12 $ fold $ map (\i -> [i..i+2]) [0..]
[0,1,2,1,2,3,2,3,4,3,4,5]
>>> sum $ take 4000000 $ fold $ map (\i -> [i..i+2]) [0..]
2666668666666

for ∷ (Traversable t, Applicative f) ⇒ t a → (a → f b) → f (t b) Source #

for is traverse with its arguments flipped. For a version that ignores the results see for_.

throw ∷ ∀ (r ∷ RuntimeRep) (a ∷ TYPE r) e. Exception e ⇒ e → a Source #

Throw an exception. Exceptions may be thrown from purely functional code, but may only be caught within the IO monad.

WARNING: You may want to use throwIO instead so that your pure code stays exception-free.

joinMonad m ⇒ m (m a) → m a Source #

The join function is the conventional monad join operator. It is used to remove one level of monadic structure, projecting its bound argument into the outer level.

'join bss' can be understood as the do expression

do bs <- bss
   bs

Examples

Expand

A common use of join is to run an IO computation returned from an STM transaction, since STM transactions can't perform IO directly. Recall that

atomically :: STM a -> IO a

is used to run STM transactions atomically. So, by specializing the types of atomically and join to

atomically :: STM (IO b) -> IO (IO b)
join       :: IO (IO b)  -> IO b

we can compose them as

join . atomically :: STM (IO b) -> IO b

to run an STM transaction and the IO action it returns.

(<=<)Monad m ⇒ (b → m c) → (a → m b) → a → m c infixr 1 Source #

Right-to-left composition of Kleisli arrows. (>=>), with the arguments flipped.

Note how this operator resembles function composition (.):

(.)   ::            (b ->   c) -> (a ->   b) -> a ->   c
(<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c

(>=>)Monad m ⇒ (a → m b) → (b → m c) → a → m c infixr 1 Source #

Left-to-right composition of Kleisli arrows.

'(bs >=> cs) a' can be understood as the do expression

do b <- bs a
   cs b

($>)Functor f ⇒ f a → b → f b infixl 4 Source #

Flipped version of <$.

Examples

Expand

Replace the contents of a Maybe Int with a constant String:

>>> Nothing $> "foo"
Nothing
>>> Just 90210 $> "foo"
Just "foo"

Replace the contents of an Either Int Int with a constant String, resulting in an Either Int String:

>>> Left 8675309 $> "foo"
Left 8675309
>>> Right 8675309 $> "foo"
Right "foo"

Replace each element of a list with a constant String:

>>> [1,2,3] $> "foo"
["foo","foo","foo"]

Replace the second element of a pair with a constant String:

>>> (1,2) $> "foo"
(1,"foo")

Since: base-4.7.0.0

fromRight ∷ b → Either a b → b Source #

Return the contents of a Right-value or a default value otherwise.

Examples

Expand

Basic usage:

>>> fromRight 1 (Right 3)
3
>>> fromRight 1 (Left "foo")
1

Since: base-4.10.0.0

isRightEither a b → Bool Source #

Return True if the given value is a Right-value, False otherwise.

Examples

Expand

Basic usage:

>>> isRight (Left "foo")
False
>>> isRight (Right 3)
True

Assuming a Left value signifies some sort of error, we can use isRight to write a very simple reporting function that only outputs "SUCCESS" when a computation has succeeded.

This example shows how isRight might be used to avoid pattern matching when one does not care about the value contained in the constructor:

>>> import Control.Monad ( when )
>>> let report e = when (isRight e) $ putStrLn "SUCCESS"
>>> report (Left "parse error")
>>> report (Right 1)
SUCCESS

Since: base-4.7.0.0

isLeftEither a b → Bool Source #

Return True if the given value is a Left-value, False otherwise.

Examples

Expand

Basic usage:

>>> isLeft (Left "foo")
True
>>> isLeft (Right 3)
False

Assuming a Left value signifies some sort of error, we can use isLeft to write a very simple error-reporting function that does absolutely nothing in the case of success, and outputs "ERROR" if any error occurred.

This example shows how isLeft might be used to avoid pattern matching when one does not care about the value contained in the constructor:

>>> import Control.Monad ( when )
>>> let report e = when (isLeft e) $ putStrLn "ERROR"
>>> report (Right 1)
>>> report (Left "parse error")
ERROR

Since: base-4.7.0.0

voidFunctor f ⇒ f a → f () Source #

void value discards or ignores the result of evaluation, such as the return value of an IO action.

Examples

Expand

Replace the contents of a Maybe Int with unit:

>>> void Nothing
Nothing
>>> void (Just 3)
Just ()

Replace the contents of an Either Int Int with unit, resulting in an Either Int ():

>>> void (Left 8675309)
Left 8675309
>>> void (Right 8675309)
Right ()

Replace every element of a list with unit:

>>> void [1,2,3]
[(),(),()]

Replace the second element of a pair with unit:

>>> void (1,2)
(1,())

Discard the result of an IO action:

>>> mapM print [1,2]
1
2
[(),()]
>>> void $ mapM print [1,2]
1
2

throughFunctor f ⇒ (a → f b) → a → f a Source #

Makes an effectful function ignore its result value and return its input value.

coerce ∷ ∀ {k ∷ RuntimeRep} (a ∷ TYPE k) (b ∷ TYPE k). Coercible a b ⇒ a → b Source #

The function coerce allows you to safely convert between values of types that have the same representation with no run-time overhead. In the simplest case you can use it instead of a newtype constructor, to go from the newtype's concrete type to the abstract type. But it also works in more complicated settings, e.g. converting a list of newtypes to a list of concrete types.

When used in conversions involving a newtype wrapper, make sure the newtype constructor is in scope.

This function is representation-polymorphic, but the RuntimeRep type argument is marked as Inferred, meaning that it is not available for visible type application. This means the typechecker will accept coerce @Int @Age 42.

Examples

Expand
>>> newtype TTL = TTL Int deriving (Eq, Ord, Show)
>>> newtype Age = Age Int deriving (Eq, Ord, Show)
>>> coerce (Age 42) :: TTL
TTL 42
>>> coerce (+ (1 :: Int)) (Age 42) :: TTL
TTL 43
>>> coerce (map (+ (1 :: Int))) [Age 42, Age 24] :: [TTL]
[TTL 43,TTL 25]

coerceViaCoercible a b ⇒ (a → b) → a → b Source #

Coerce the second argument to the result type of the first one. The motivation for this function is that it's often more annoying to explicitly specify a target type for coerce than to construct an explicit coercion function, so this combinator can be used in cases like that. Plus the code reads better, as it becomes clear what and where gets wrapped/unwrapped.

coerceArgCoercible a b ⇒ (a → s) → b → s Source #

Same as f -> f . coerce, but does not create any closures and so is completely free.

coerceResCoercible s t ⇒ (a → s) → a → t Source #

Same as f -> coerce . f, but does not create any closures and so is completely free.

class Generic a Source #

Representable types of kind *. This class is derivable in GHC with the DeriveGeneric flag on.

A Generic instance must satisfy the following laws:

from . toid
to . fromid

Minimal complete definition

from, to

Instances

Instances details
Generic Value 
Instance details

Defined in Data.Aeson.Types.Internal

Associated Types

type Rep Value ∷ TypeType Source #

Methods

from ∷ Value → Rep Value x Source #

toRep Value x → Value Source #

Generic All 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep AllTypeType Source #

Methods

fromAllRep All x Source #

toRep All x → All Source #

Generic Any 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep AnyTypeType Source #

Methods

fromAnyRep Any x Source #

toRep Any x → Any Source #

Generic Version 
Instance details

Defined in Data.Version

Associated Types

type Rep VersionTypeType Source #

Methods

fromVersionRep Version x Source #

toRep Version x → Version Source #

Generic Void 
Instance details

Defined in GHC.Generics

Associated Types

type Rep VoidTypeType Source #

Methods

fromVoidRep Void x Source #

toRep Void x → Void Source #

Generic ByteOrder 
Instance details

Defined in GHC.ByteOrder

Associated Types

type Rep ByteOrderTypeType Source #

Generic Fingerprint 
Instance details

Defined in GHC.Generics

Associated Types

type Rep FingerprintTypeType Source #

Generic Associativity 
Instance details

Defined in GHC.Generics

Associated Types

type Rep AssociativityTypeType Source #

Generic DecidedStrictness 
Instance details

Defined in GHC.Generics

Associated Types

type Rep DecidedStrictnessTypeType Source #

Generic Fixity 
Instance details

Defined in GHC.Generics

Associated Types

type Rep FixityTypeType Source #

Methods

fromFixityRep Fixity x Source #

toRep Fixity x → Fixity Source #

Generic SourceStrictness 
Instance details

Defined in GHC.Generics

Associated Types

type Rep SourceStrictnessTypeType Source #

Generic SourceUnpackedness 
Instance details

Defined in GHC.Generics

Associated Types

type Rep SourceUnpackednessTypeType Source #

Generic ExitCode 
Instance details

Defined in GHC.IO.Exception

Associated Types

type Rep ExitCodeTypeType Source #

Generic CCFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep CCFlagsTypeType Source #

Methods

fromCCFlagsRep CCFlags x Source #

toRep CCFlags x → CCFlags Source #

Generic ConcFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep ConcFlagsTypeType Source #

Generic DebugFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep DebugFlagsTypeType Source #

Generic DoCostCentres 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep DoCostCentresTypeType Source #

Generic DoHeapProfile 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep DoHeapProfileTypeType Source #

Generic DoTrace 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep DoTraceTypeType Source #

Methods

fromDoTraceRep DoTrace x Source #

toRep DoTrace x → DoTrace Source #

Generic GCFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep GCFlagsTypeType Source #

Methods

fromGCFlagsRep GCFlags x Source #

toRep GCFlags x → GCFlags Source #

Generic GiveGCStats 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep GiveGCStatsTypeType Source #

Generic MiscFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep MiscFlagsTypeType Source #

Generic ParFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep ParFlagsTypeType Source #

Generic ProfFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep ProfFlagsTypeType Source #

Generic RTSFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep RTSFlagsTypeType Source #

Generic TickyFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep TickyFlagsTypeType Source #

Generic TraceFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep TraceFlagsTypeType Source #

Generic SrcLoc 
Instance details

Defined in GHC.Generics

Associated Types

type Rep SrcLocTypeType Source #

Methods

fromSrcLocRep SrcLoc x Source #

toRep SrcLoc x → SrcLoc Source #

Generic GCDetails 
Instance details

Defined in GHC.Stats

Associated Types

type Rep GCDetailsTypeType Source #

Generic RTSStats 
Instance details

Defined in GHC.Stats

Associated Types

type Rep RTSStatsTypeType Source #

Generic GeneralCategory 
Instance details

Defined in GHC.Generics

Associated Types

type Rep GeneralCategoryTypeType Source #

Generic OsChar 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Associated Types

type Rep OsCharTypeType Source #

Methods

fromOsCharRep OsChar x Source #

toRep OsChar x → OsChar Source #

Generic OsString 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Associated Types

type Rep OsStringTypeType Source #

Generic PosixChar 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Associated Types

type Rep PosixCharTypeType Source #

Generic PosixString 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Associated Types

type Rep PosixStringTypeType Source #

Generic WindowsChar 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Associated Types

type Rep WindowsCharTypeType Source #

Generic WindowsString 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Associated Types

type Rep WindowsStringTypeType Source #

Generic Filler 
Instance details

Defined in Flat.Filler

Associated Types

type Rep FillerTypeType Source #

Methods

fromFillerRep Filler x Source #

toRep Filler x → Filler Source #

Generic ForeignSrcLang 
Instance details

Defined in GHC.ForeignSrcLang.Type

Associated Types

type Rep ForeignSrcLangTypeType Source #

Generic Extension 
Instance details

Defined in GHC.LanguageExtensions.Type

Associated Types

type Rep ExtensionTypeType Source #

Generic ClosureType 
Instance details

Defined in GHC.Exts.Heap.ClosureTypes

Associated Types

type Rep ClosureTypeTypeType Source #

Generic PrimType 
Instance details

Defined in GHC.Exts.Heap.Closures

Associated Types

type Rep PrimTypeTypeType Source #

Generic TsoFlags 
Instance details

Defined in GHC.Exts.Heap.Closures

Associated Types

type Rep TsoFlagsTypeType Source #

Generic WhatNext 
Instance details

Defined in GHC.Exts.Heap.Closures

Associated Types

type Rep WhatNextTypeType Source #

Generic WhyBlocked 
Instance details

Defined in GHC.Exts.Heap.Closures

Associated Types

type Rep WhyBlockedTypeType Source #

Generic StgInfoTable 
Instance details

Defined in GHC.Exts.Heap.InfoTable.Types

Associated Types

type Rep StgInfoTableTypeType Source #

Generic CostCentre 
Instance details

Defined in GHC.Exts.Heap.ProfInfo.Types

Associated Types

type Rep CostCentreTypeType Source #

Generic CostCentreStack 
Instance details

Defined in GHC.Exts.Heap.ProfInfo.Types

Associated Types

type Rep CostCentreStackTypeType Source #

Generic IndexTable 
Instance details

Defined in GHC.Exts.Heap.ProfInfo.Types

Associated Types

type Rep IndexTableTypeType Source #

Generic StgTSOProfInfo 
Instance details

Defined in GHC.Exts.Heap.ProfInfo.Types

Associated Types

type Rep StgTSOProfInfoTypeType Source #

Generic Ordering 
Instance details

Defined in GHC.Generics

Associated Types

type Rep OrderingTypeType Source #

Generic Half 
Instance details

Defined in Numeric.Half.Internal

Associated Types

type Rep Half ∷ TypeType Source #

Methods

from ∷ Half → Rep Half x Source #

toRep Half x → Half Source #

Generic InvalidPosException 
Instance details

Defined in Text.Megaparsec.Pos

Associated Types

type Rep InvalidPosExceptionTypeType 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 #

Generic SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Associated Types

type Rep SourcePosTypeType Source #

Generic URI 
Instance details

Defined in Network.URI

Associated Types

type Rep URI ∷ TypeType Source #

Methods

from ∷ URI → Rep URI x Source #

toRep URI x → URI Source #

Generic URIAuth 
Instance details

Defined in Network.URI

Associated Types

type Rep URIAuth ∷ TypeType Source #

Methods

from ∷ URIAuth → Rep URIAuth x Source #

toRep URIAuth x → URIAuth Source #

Generic OsChar 
Instance details

Defined in System.OsString.Internal.Types

Associated Types

type Rep OsChar ∷ TypeType Source #

Methods

from ∷ OsChar → Rep OsChar x Source #

toRep OsChar x → OsChar Source #

Generic OsString 
Instance details

Defined in System.OsString.Internal.Types

Associated Types

type Rep OsString ∷ TypeType Source #

Methods

from ∷ OsString → Rep OsString x Source #

toRep OsString x → OsString Source #

Generic PosixChar 
Instance details

Defined in System.OsString.Internal.Types

Associated Types

type Rep PosixChar ∷ TypeType Source #

Methods

from ∷ PosixChar → Rep PosixChar x Source #

toRep PosixChar x → PosixChar Source #

Generic PosixString 
Instance details

Defined in System.OsString.Internal.Types

Associated Types

type Rep PosixString ∷ TypeType Source #

Methods

from ∷ PosixString → Rep PosixString x Source #

toRep PosixString x → PosixString Source #

Generic WindowsChar 
Instance details

Defined in System.OsString.Internal.Types

Associated Types

type Rep WindowsChar ∷ TypeType Source #

Methods

from ∷ WindowsChar → Rep WindowsChar x Source #

toRep WindowsChar x → WindowsChar Source #

Generic WindowsString 
Instance details

Defined in System.OsString.Internal.Types

Associated Types

type Rep WindowsString ∷ TypeType Source #

Methods

from ∷ WindowsString → Rep WindowsString x Source #

toRep WindowsString x → WindowsString Source #

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 #

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 #

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 #

Generic SrcSpans Source # 
Instance details

Defined in PlutusCore.Annotation

Associated Types

type Rep SrcSpansTypeType Source #

Generic Data Source # 
Instance details

Defined in PlutusCore.Data

Associated Types

type Rep DataTypeType Source #

Methods

fromDataRep Data x Source #

toRep Data x → Data Source #

Generic DeBruijn Source # 
Instance details

Defined in PlutusCore.DeBruijn.Internal

Associated Types

type Rep DeBruijnTypeType Source #

Generic FreeVariableError Source # 
Instance details

Defined in PlutusCore.DeBruijn.Internal

Associated Types

type Rep FreeVariableErrorTypeType Source #

Generic Index Source # 
Instance details

Defined in PlutusCore.DeBruijn.Internal

Associated Types

type Rep IndexTypeType Source #

Methods

fromIndexRep Index x Source #

toRep Index x → Index Source #

Generic NamedDeBruijn Source # 
Instance details

Defined in PlutusCore.DeBruijn.Internal

Associated Types

type Rep NamedDeBruijnTypeType Source #

Generic NamedTyDeBruijn Source # 
Instance details

Defined in PlutusCore.DeBruijn.Internal

Associated Types

type Rep NamedTyDeBruijnTypeType Source #

Generic TyDeBruijn Source # 
Instance details

Defined in PlutusCore.DeBruijn.Internal

Associated Types

type Rep TyDeBruijnTypeType Source #

Generic DefaultFun Source # 
Instance details

Defined in PlutusCore.Default.Builtins

Associated Types

type Rep DefaultFunTypeType Source #

Generic ParserError Source # 
Instance details

Defined in PlutusCore.Error

Associated Types

type Rep ParserErrorTypeType Source #

Generic ParserErrorBundle Source # 
Instance details

Defined in PlutusCore.Error

Associated Types

type Rep ParserErrorBundleTypeType Source #

Generic CostModelApplyError Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostModelInterface

Associated Types

type Rep CostModelApplyErrorTypeType Source #

Generic Coefficient0 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep Coefficient0TypeType Source #

Generic Coefficient00 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep Coefficient00TypeType Source #

Generic Coefficient01 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep Coefficient01TypeType Source #

Generic Coefficient02 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep Coefficient02TypeType Source #

Generic Coefficient1 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep Coefficient1TypeType Source #

Generic Coefficient10 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep Coefficient10TypeType Source #

Generic Coefficient11 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep Coefficient11TypeType Source #

Generic Coefficient2 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep Coefficient2TypeType Source #

Generic Coefficient20 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep Coefficient20TypeType Source #

Generic Intercept Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep InterceptTypeType Source #

Generic ModelConstantOrLinear Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep ModelConstantOrLinearTypeType Source #

Generic ModelConstantOrOneArgument Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep ModelConstantOrOneArgumentTypeType Source #

Generic ModelConstantOrTwoArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep ModelConstantOrTwoArgumentsTypeType Source #

Generic ModelFiveArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep ModelFiveArgumentsTypeType Source #

Generic ModelFourArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep ModelFourArgumentsTypeType Source #

Generic ModelOneArgument Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep ModelOneArgumentTypeType Source #

Generic ModelSixArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep ModelSixArgumentsTypeType Source #

Generic ModelSubtractedSizes Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep ModelSubtractedSizesTypeType Source #

Generic ModelThreeArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep ModelThreeArgumentsTypeType Source #

Generic ModelTwoArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep ModelTwoArgumentsTypeType Source #

Generic OneVariableLinearFunction Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep OneVariableLinearFunctionTypeType Source #

Generic OneVariableQuadraticFunction Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep OneVariableQuadraticFunctionTypeType Source #

Generic Slope Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep SlopeTypeType Source #

Methods

fromSlopeRep Slope x Source #

toRep Slope x → Slope Source #

Generic TwoVariableLinearFunction Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep TwoVariableLinearFunctionTypeType Source #

Generic TwoVariableQuadraticFunction Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep TwoVariableQuadraticFunctionTypeType Source #

Generic ExBudget Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

Associated Types

type Rep ExBudgetTypeType Source #

Generic ExCPU Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Associated Types

type Rep ExCPUTypeType Source #

Methods

fromExCPURep ExCPU x Source #

toRep ExCPU x → ExCPU Source #

Generic ExMemory Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Associated Types

type Rep ExMemoryTypeType Source #

Generic ExtensionFun Source # 
Instance details

Defined in PlutusCore.Examples.Builtins

Associated Types

type Rep ExtensionFunTypeType Source #

Generic Name Source # 
Instance details

Defined in PlutusCore.Name.Unique

Associated Types

type Rep NameTypeType Source #

Methods

fromNameRep Name x Source #

toRep Name x → Name Source #

Generic TyName Source # 
Instance details

Defined in PlutusCore.Name.Unique

Associated Types

type Rep TyNameTypeType Source #

Methods

fromTyNameRep TyName x Source #

toRep TyName x → TyName Source #

Generic Version Source # 
Instance details

Defined in PlutusCore.Version

Associated Types

type Rep VersionTypeType Source #

Methods

fromVersionRep Version x Source #

toRep Version x → Version Source #

Generic CekUserError Source # 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Associated Types

type Rep CekUserErrorTypeType Source #

Generic StepKind Source # 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Associated Types

type Rep StepKindTypeType Source #

Generic SatInt 
Instance details

Defined in Data.SatInt

Associated Types

type Rep SatIntTypeType Source #

Methods

fromSatIntRep SatInt x Source #

toRep SatInt x → SatInt Source #

Generic Mode 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep ModeTypeType Source #

Methods

fromModeRep Mode x Source #

toRep Mode x → Mode Source #

Generic Style 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep StyleTypeType Source #

Methods

fromStyleRep Style x Source #

toRep Style x → Style Source #

Generic TextDetails 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep TextDetailsTypeType Source #

Generic Doc 
Instance details

Defined in Text.PrettyPrint.HughesPJ

Associated Types

type Rep DocTypeType Source #

Methods

fromDocRep Doc x Source #

toRep Doc x → Doc Source #

Generic AnnLookup 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep AnnLookupTypeType Source #

Generic AnnTarget 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep AnnTargetTypeType Source #

Generic Bang 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep BangTypeType Source #

Methods

fromBangRep Bang x Source #

toRep Bang x → Bang Source #

Generic Body 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep BodyTypeType Source #

Methods

fromBodyRep Body x Source #

toRep Body x → Body Source #

Generic Bytes 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep BytesTypeType Source #

Methods

fromBytesRep Bytes x Source #

toRep Bytes x → Bytes Source #

Generic Callconv 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep CallconvTypeType Source #

Generic Clause 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep ClauseTypeType Source #

Methods

fromClauseRep Clause x Source #

toRep Clause x → Clause Source #

Generic Con 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep ConTypeType Source #

Methods

fromConRep Con x Source #

toRep Con x → Con Source #

Generic Dec 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DecTypeType Source #

Methods

fromDecRep Dec x Source #

toRep Dec x → Dec Source #

Generic DecidedStrictness 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DecidedStrictnessTypeType Source #

Generic DerivClause 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DerivClauseTypeType Source #

Generic DerivStrategy 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DerivStrategyTypeType Source #

Generic DocLoc 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DocLocTypeType Source #

Methods

fromDocLocRep DocLoc x Source #

toRep DocLoc x → DocLoc Source #

Generic Exp 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep ExpTypeType Source #

Methods

fromExpRep Exp x Source #

toRep Exp x → Exp Source #

Generic FamilyResultSig 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep FamilyResultSigTypeType Source #

Generic Fixity 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep FixityTypeType Source #

Methods

fromFixityRep Fixity x Source #

toRep Fixity x → Fixity Source #

Generic FixityDirection 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep FixityDirectionTypeType Source #

Generic Foreign 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep ForeignTypeType Source #

Methods

fromForeignRep Foreign x Source #

toRep Foreign x → Foreign Source #

Generic FunDep 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep FunDepTypeType Source #

Methods

fromFunDepRep FunDep x Source #

toRep FunDep x → FunDep Source #

Generic Guard 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep GuardTypeType Source #

Methods

fromGuardRep Guard x Source #

toRep Guard x → Guard Source #

Generic Info 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep InfoTypeType Source #

Methods

fromInfoRep Info x Source #

toRep Info x → Info Source #

Generic InjectivityAnn 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep InjectivityAnnTypeType Source #

Generic Inline 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep InlineTypeType Source #

Methods

fromInlineRep Inline x Source #

toRep Inline x → Inline Source #

Generic Lit 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep LitTypeType Source #

Methods

fromLitRep Lit x Source #

toRep Lit x → Lit Source #

Generic Loc 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep LocTypeType Source #

Methods

fromLocRep Loc x Source #

toRep Loc x → Loc Source #

Generic Match 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep MatchTypeType Source #

Methods

fromMatchRep Match x Source #

toRep Match x → Match Source #

Generic ModName 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep ModNameTypeType Source #

Methods

fromModNameRep ModName x Source #

toRep ModName x → ModName Source #

Generic Module 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep ModuleTypeType Source #

Methods

fromModuleRep Module x Source #

toRep Module x → Module Source #

Generic ModuleInfo 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep ModuleInfoTypeType Source #

Generic Name 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep NameTypeType Source #

Methods

fromNameRep Name x Source #

toRep Name x → Name Source #

Generic NameFlavour 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep NameFlavourTypeType Source #

Generic NameSpace 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep NameSpaceTypeType Source #

Generic OccName 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep OccNameTypeType Source #

Methods

fromOccNameRep OccName x Source #

toRep OccName x → OccName Source #

Generic Overlap 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep OverlapTypeType Source #

Methods

fromOverlapRep Overlap x Source #

toRep Overlap x → Overlap Source #

Generic Pat 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PatTypeType Source #

Methods

fromPatRep Pat x Source #

toRep Pat x → Pat Source #

Generic PatSynArgs 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PatSynArgsTypeType Source #

Generic PatSynDir 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PatSynDirTypeType Source #

Generic Phases 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PhasesTypeType Source #

Methods

fromPhasesRep Phases x Source #

toRep Phases x → Phases Source #

Generic PkgName 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PkgNameTypeType Source #

Methods

fromPkgNameRep PkgName x Source #

toRep PkgName x → PkgName Source #

Generic Pragma 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PragmaTypeType Source #

Methods

fromPragmaRep Pragma x Source #

toRep Pragma x → Pragma Source #

Generic Range 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep RangeTypeType Source #

Methods

fromRangeRep Range x Source #

toRep Range x → Range Source #

Generic Role 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep RoleTypeType Source #

Methods

fromRoleRep Role x Source #

toRep Role x → Role Source #

Generic RuleBndr 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep RuleBndrTypeType Source #

Generic RuleMatch 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep RuleMatchTypeType Source #

Generic Safety 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep SafetyTypeType Source #

Methods

fromSafetyRep Safety x Source #

toRep Safety x → Safety Source #

Generic SourceStrictness 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep SourceStrictnessTypeType Source #

Generic SourceUnpackedness 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep SourceUnpackednessTypeType Source #

Generic Specificity 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep SpecificityTypeType Source #

Generic Stmt 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep StmtTypeType Source #

Methods

fromStmtRep Stmt x Source #

toRep Stmt x → Stmt Source #

Generic TyLit 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TyLitTypeType Source #

Methods

fromTyLitRep TyLit x Source #

toRep TyLit x → TyLit Source #

Generic TySynEqn 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TySynEqnTypeType Source #

Generic Type 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TypeTypeType Source #

Methods

fromTypeRep Type x Source #

toRep Type x → Type Source #

Generic TypeFamilyHead 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TypeFamilyHeadTypeType Source #

Generic ConstructorInfo 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep ConstructorInfoTypeType Source #

Generic ConstructorVariant 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep ConstructorVariantTypeType Source #

Generic DatatypeInfo 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep DatatypeInfoTypeType Source #

Generic DatatypeVariant 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep DatatypeVariantTypeType Source #

Generic FieldStrictness 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep FieldStrictnessTypeType Source #

Generic Strictness 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep StrictnessTypeType Source #

Generic Unpackedness 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep UnpackednessTypeType Source #

Generic () 
Instance details

Defined in GHC.Generics

Associated Types

type Rep () ∷ TypeType Source #

Methods

from ∷ () → Rep () x Source #

toRep () x → () Source #

Generic Bool 
Instance details

Defined in GHC.Generics

Associated Types

type Rep BoolTypeType Source #

Methods

fromBoolRep Bool x Source #

toRep Bool x → Bool Source #

Generic (Only a) 
Instance details

Defined in Data.Tuple.Only

Associated Types

type Rep (Only a) ∷ TypeType Source #

Methods

from ∷ Only a → Rep (Only a) x Source #

toRep (Only a) x → Only a Source #

Generic (ZipList a) 
Instance details

Defined in Control.Applicative

Associated Types

type Rep (ZipList a) ∷ TypeType Source #

Methods

fromZipList a → Rep (ZipList a) x Source #

toRep (ZipList a) x → ZipList a Source #

Generic (Complex a) 
Instance details

Defined in Data.Complex

Associated Types

type Rep (Complex a) ∷ TypeType Source #

Methods

fromComplex a → Rep (Complex a) x Source #

toRep (Complex a) x → Complex a Source #

Generic (Identity a) 
Instance details

Defined in Data.Functor.Identity

Associated Types

type Rep (Identity a) ∷ TypeType Source #

Methods

fromIdentity a → Rep (Identity a) x Source #

toRep (Identity a) x → Identity a Source #

Generic (First a) 
Instance details

Defined in Data.Monoid

Associated Types

type Rep (First a) ∷ TypeType Source #

Methods

fromFirst a → Rep (First a) x Source #

toRep (First a) x → First a Source #

Generic (Last a) 
Instance details

Defined in Data.Monoid

Associated Types

type Rep (Last a) ∷ TypeType Source #

Methods

fromLast a → Rep (Last a) x Source #

toRep (Last a) x → Last a Source #

Generic (Down a) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Down a) ∷ TypeType Source #

Methods

fromDown a → Rep (Down a) x Source #

toRep (Down a) x → Down a Source #

Generic (First a) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (First a) ∷ TypeType Source #

Methods

fromFirst a → Rep (First a) x Source #

toRep (First a) x → First a Source #

Generic (Last a) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Last a) ∷ TypeType Source #

Methods

fromLast a → Rep (Last a) x Source #

toRep (Last a) x → Last a Source #

Generic (Max a) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Max a) ∷ TypeType Source #

Methods

fromMax a → Rep (Max a) x Source #

toRep (Max a) x → Max a Source #

Generic (Min a) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Min a) ∷ TypeType Source #

Methods

fromMin a → Rep (Min a) x Source #

toRep (Min a) x → Min a Source #

Generic (WrappedMonoid m) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (WrappedMonoid m) ∷ TypeType Source #

Generic (Dual a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Dual a) ∷ TypeType Source #

Methods

fromDual a → Rep (Dual a) x Source #

toRep (Dual a) x → Dual a Source #

Generic (Endo a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Endo a) ∷ TypeType Source #

Methods

fromEndo a → Rep (Endo a) x Source #

toRep (Endo a) x → Endo a Source #

Generic (Product a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Product a) ∷ TypeType Source #

Methods

fromProduct a → Rep (Product a) x Source #

toRep (Product a) x → Product a Source #

Generic (Sum a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Sum a) ∷ TypeType Source #

Methods

fromSum a → Rep (Sum a) x Source #

toRep (Sum a) x → Sum a Source #

Generic (NonEmpty a) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (NonEmpty a) ∷ TypeType Source #

Methods

fromNonEmpty a → Rep (NonEmpty a) x Source #

toRep (NonEmpty a) x → NonEmpty a Source #

Generic (Par1 p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Par1 p) ∷ TypeType Source #

Methods

fromPar1 p → Rep (Par1 p) x Source #

toRep (Par1 p) x → Par1 p Source #

Generic (SigDSIGN EcdsaSecp256k1DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.EcdsaSecp256k1

Associated Types

type Rep (SigDSIGN EcdsaSecp256k1DSIGN) ∷ TypeType Source #

Generic (SigDSIGN Ed25519DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Ed25519

Associated Types

type Rep (SigDSIGN Ed25519DSIGN) ∷ TypeType Source #

Generic (SigDSIGN SchnorrSecp256k1DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.SchnorrSecp256k1

Associated Types

type Rep (SigDSIGN SchnorrSecp256k1DSIGN) ∷ TypeType Source #

Generic (SignKeyDSIGN EcdsaSecp256k1DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.EcdsaSecp256k1

Associated Types

type Rep (SignKeyDSIGN EcdsaSecp256k1DSIGN) ∷ TypeType Source #

Generic (SignKeyDSIGN Ed25519DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Ed25519

Associated Types

type Rep (SignKeyDSIGN Ed25519DSIGN) ∷ TypeType Source #

Generic (SignKeyDSIGN SchnorrSecp256k1DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.SchnorrSecp256k1

Associated Types

type Rep (SignKeyDSIGN SchnorrSecp256k1DSIGN) ∷ TypeType Source #

Generic (VerKeyDSIGN EcdsaSecp256k1DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.EcdsaSecp256k1

Associated Types

type Rep (VerKeyDSIGN EcdsaSecp256k1DSIGN) ∷ TypeType Source #

Generic (VerKeyDSIGN Ed25519DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Ed25519

Associated Types

type Rep (VerKeyDSIGN Ed25519DSIGN) ∷ TypeType Source #

Generic (VerKeyDSIGN SchnorrSecp256k1DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.SchnorrSecp256k1

Associated Types

type Rep (VerKeyDSIGN SchnorrSecp256k1DSIGN) ∷ TypeType Source #

Generic (Digit a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (Digit a) ∷ TypeType Source #

Methods

fromDigit a → Rep (Digit a) x Source #

toRep (Digit a) x → Digit a Source #

Generic (Elem a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (Elem a) ∷ TypeType Source #

Methods

fromElem a → Rep (Elem a) x Source #

toRep (Elem a) x → Elem a Source #

Generic (FingerTree a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (FingerTree a) ∷ TypeType Source #

Methods

fromFingerTree a → Rep (FingerTree a) x Source #

toRep (FingerTree a) x → FingerTree a Source #

Generic (Node a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (Node a) ∷ TypeType Source #

Methods

fromNode a → Rep (Node a) x Source #

toRep (Node a) x → Node a Source #

Generic (ViewL a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (ViewL a) ∷ TypeType Source #

Methods

fromViewL a → Rep (ViewL a) x Source #

toRep (ViewL a) x → ViewL a Source #

Generic (ViewR a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (ViewR a) ∷ TypeType Source #

Methods

fromViewR a → Rep (ViewR a) x Source #

toRep (ViewR a) x → ViewR a Source #

Generic (Tree a) 
Instance details

Defined in Data.Tree

Associated Types

type Rep (Tree a) ∷ TypeType Source #

Methods

fromTree a → Rep (Tree a) x Source #

toRep (Tree a) x → Tree a Source #

Generic (Fix f) 
Instance details

Defined in Data.Fix

Associated Types

type Rep (Fix f) ∷ TypeType Source #

Methods

from ∷ Fix f → Rep (Fix f) x Source #

toRep (Fix f) x → Fix f Source #

Generic (PostAligned a) 
Instance details

Defined in Flat.Filler

Associated Types

type Rep (PostAligned a) ∷ TypeType Source #

Methods

fromPostAligned a → Rep (PostAligned a) x Source #

toRep (PostAligned a) x → PostAligned a Source #

Generic (PreAligned a) 
Instance details

Defined in Flat.Filler

Associated Types

type Rep (PreAligned a) ∷ TypeType Source #

Methods

fromPreAligned a → Rep (PreAligned a) x Source #

toRep (PreAligned a) x → PreAligned a Source #

Generic (GenClosure b) 
Instance details

Defined in GHC.Exts.Heap.Closures

Associated Types

type Rep (GenClosure b) ∷ TypeType Source #

Methods

fromGenClosure b → Rep (GenClosure b) x Source #

toRep (GenClosure b) x → GenClosure b Source #

Generic (ErrorFancy e) 
Instance details

Defined in Text.Megaparsec.Error

Associated Types

type Rep (ErrorFancy e) ∷ TypeType Source #

Methods

fromErrorFancy e → Rep (ErrorFancy e) x Source #

toRep (ErrorFancy e) x → ErrorFancy e Source #

Generic (ErrorItem t) 
Instance details

Defined in Text.Megaparsec.Error

Associated Types

type Rep (ErrorItem t) ∷ TypeType Source #

Methods

fromErrorItem t → Rep (ErrorItem t) x Source #

toRep (ErrorItem t) x → ErrorItem t Source #

Generic (PosState s) 
Instance details

Defined in Text.Megaparsec.State

Associated Types

type Rep (PosState s) ∷ TypeType Source #

Methods

fromPosState s → Rep (PosState s) x Source #

toRep (PosState s) x → PosState s Source #

Generic (BuiltinSemanticsVariant DefaultFun) Source # 
Instance details

Defined in PlutusCore.Default.Builtins

Associated Types

type Rep (BuiltinSemanticsVariant DefaultFun) ∷ TypeType Source #

Generic (Kind ann) Source # 
Instance details

Defined in PlutusCore.Core.Type

Associated Types

type Rep (Kind ann) ∷ TypeType Source #

Methods

fromKind ann → Rep (Kind ann) x Source #

toRep (Kind ann) x → Kind ann Source #

Generic (Normalized a) Source # 
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 #

Generic (LR a) Source # 
Instance details

Defined in PlutusCore.Eq

Associated Types

type Rep (LR a) ∷ TypeType Source #

Methods

fromLR a → Rep (LR a) x Source #

toRep (LR a) x → LR a Source #

Generic (RL a) Source # 
Instance details

Defined in PlutusCore.Eq

Associated Types

type Rep (RL a) ∷ TypeType Source #

Methods

fromRL a → Rep (RL a) x Source #

toRep (RL a) x → RL a Source #

Generic (ExpectedShapeOr a) Source # 
Instance details

Defined in PlutusCore.Error

Associated Types

type Rep (ExpectedShapeOr a) ∷ TypeType Source #

Generic (UniqueError ann) Source # 
Instance details

Defined in PlutusCore.Error

Associated Types

type Rep (UniqueError ann) ∷ TypeType Source #

Methods

fromUniqueError ann → Rep (UniqueError ann) x Source #

toRep (UniqueError ann) x → UniqueError ann Source #

Generic (BuiltinCostModelBase f) Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

Associated Types

type Rep (BuiltinCostModelBase f) ∷ TypeType Source #

Generic (CostingFun model) Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep (CostingFun model) ∷ TypeType Source #

Methods

fromCostingFun model → Rep (CostingFun model) x Source #

toRep (CostingFun model) x → CostingFun model Source #

Generic (MachineError fun) Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

Associated Types

type Rep (MachineError fun) ∷ TypeType Source #

Methods

fromMachineError fun → Rep (MachineError fun) x Source #

toRep (MachineError fun) x → MachineError fun Source #

Generic (EvaluationResult a) Source # 
Instance details

Defined in PlutusCore.Evaluation.Result

Associated Types

type Rep (EvaluationResult a) ∷ TypeType Source #

Generic (CekMachineCostsBase f) Source # 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.CekMachineCosts

Associated Types

type Rep (CekMachineCostsBase f) ∷ TypeType Source #

Generic (CekExTally fun) Source # 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

Associated Types

type Rep (CekExTally fun) ∷ TypeType Source #

Methods

fromCekExTally fun → Rep (CekExTally fun) x Source #

toRep (CekExTally fun) x → CekExTally fun Source #

Generic (TallyingSt fun) Source # 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

Associated Types

type Rep (TallyingSt fun) ∷ TypeType Source #

Methods

fromTallyingSt fun → Rep (TallyingSt fun) x Source #

toRep (TallyingSt fun) x → TallyingSt fun Source #

Generic (ExBudgetCategory fun) Source # 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Associated Types

type Rep (ExBudgetCategory fun) ∷ TypeType Source #

Generic (Doc a) 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep (Doc a) ∷ TypeType Source #

Methods

fromDoc a → Rep (Doc a) x Source #

toRep (Doc a) x → Doc a Source #

Generic (Doc ann) 
Instance details

Defined in Prettyprinter.Internal

Associated Types

type Rep (Doc ann) ∷ TypeType Source #

Methods

fromDoc ann → Rep (Doc ann) x Source #

toRep (Doc ann) x → Doc ann Source #

Generic (SimpleDocStream ann) 
Instance details

Defined in Prettyprinter.Internal

Associated Types

type Rep (SimpleDocStream ann) ∷ TypeType Source #

Generic (Maybe a) 
Instance details

Defined in Data.Strict.Maybe

Associated Types

type Rep (Maybe a) ∷ TypeType Source #

Methods

from ∷ Maybe a → Rep (Maybe a) x Source #

toRep (Maybe a) x → Maybe a Source #

Generic (TyVarBndr flag) 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep (TyVarBndr flag) ∷ TypeType Source #

Methods

fromTyVarBndr flag → Rep (TyVarBndr flag) x Source #

toRep (TyVarBndr flag) x → TyVarBndr flag Source #

Generic (Window a) 
Instance details

Defined in System.Console.Terminal.Common

Associated Types

type Rep (Window a) ∷ TypeType Source #

Methods

from ∷ Window a → Rep (Window a) x Source #

toRep (Window a) x → Window a Source #

Generic (Doc a) 
Instance details

Defined in Text.PrettyPrint.Annotated.WL

Associated Types

type Rep (Doc a) ∷ TypeType Source #

Methods

from ∷ Doc a → Rep (Doc a) x Source #

toRep (Doc a) x → Doc a Source #

Generic (SimpleDoc a) 
Instance details

Defined in Text.PrettyPrint.Annotated.WL

Associated Types

type Rep (SimpleDoc a) ∷ TypeType Source #

Methods

from ∷ SimpleDoc a → Rep (SimpleDoc a) x Source #

toRep (SimpleDoc a) x → SimpleDoc a Source #

Generic (Maybe a) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Maybe a) ∷ TypeType Source #

Methods

fromMaybe a → Rep (Maybe a) x Source #

toRep (Maybe a) x → Maybe a Source #

Generic (a) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a) ∷ TypeType Source #

Methods

from ∷ (a) → Rep (a) x Source #

toRep (a) x → (a) Source #

Generic [a] 
Instance details

Defined in GHC.Generics

Associated Types

type Rep [a] ∷ TypeType Source #

Methods

from ∷ [a] → Rep [a] x Source #

toRep [a] x → [a] Source #

Generic (Container b a) 
Instance details

Defined in Barbies.Internal.Containers

Associated Types

type Rep (Container b a) ∷ TypeType Source #

Methods

from ∷ Container b a → Rep (Container b a) x Source #

toRep (Container b a) x → Container b a Source #

Generic (ErrorContainer b e) 
Instance details

Defined in Barbies.Internal.Containers

Associated Types

type Rep (ErrorContainer b e) ∷ TypeType Source #

Methods

from ∷ ErrorContainer b e → Rep (ErrorContainer b e) x Source #

toRep (ErrorContainer b e) x → ErrorContainer b e Source #

Generic (Unit f) 
Instance details

Defined in Barbies.Internal.Trivial

Associated Types

type Rep (Unit f) ∷ TypeType Source #

Methods

from ∷ Unit f → Rep (Unit f) x Source #

toRep (Unit f) x → Unit f Source #

Generic (Void f) 
Instance details

Defined in Barbies.Internal.Trivial

Associated Types

type Rep (Void f) ∷ TypeType Source #

Methods

from ∷ Void f → Rep (Void f) x Source #

toRep (Void f) x → Void f Source #

Generic (WrappedMonad m a) 
Instance details

Defined in Control.Applicative

Associated Types

type Rep (WrappedMonad m a) ∷ TypeType Source #

Methods

fromWrappedMonad m a → Rep (WrappedMonad m a) x Source #

toRep (WrappedMonad m a) x → WrappedMonad m a Source #

Generic (Either a b) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Either a b) ∷ TypeType Source #

Methods

fromEither a b → Rep (Either a b) x Source #

toRep (Either a b) x → Either a b Source #

Generic (Proxy t) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Proxy t) ∷ TypeType Source #

Methods

fromProxy t → Rep (Proxy t) x Source #

toRep (Proxy t) x → Proxy t Source #

Generic (Arg a b) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Arg a b) ∷ TypeType Source #

Methods

fromArg a b → Rep (Arg a b) x Source #

toRep (Arg a b) x → Arg a b Source #

Generic (U1 p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (U1 p) ∷ TypeType Source #

Methods

fromU1 p → Rep (U1 p) x Source #

toRep (U1 p) x → U1 p Source #

Generic (V1 p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (V1 p) ∷ TypeType Source #

Methods

fromV1 p → Rep (V1 p) x Source #

toRep (V1 p) x → V1 p Source #

Generic (Bimap a b) 
Instance details

Defined in Data.Bimap

Associated Types

type Rep (Bimap a b) ∷ TypeType Source #

Methods

from ∷ Bimap a b → Rep (Bimap a b) x Source #

toRep (Bimap a b) x → Bimap a b Source #

Generic (SignedDSIGN v a) 
Instance details

Defined in Cardano.Crypto.DSIGN.Class

Associated Types

type Rep (SignedDSIGN v a) ∷ TypeType Source #

Methods

fromSignedDSIGN v a → Rep (SignedDSIGN v a) x Source #

toRep (SignedDSIGN v a) x → SignedDSIGN v a Source #

Generic (Hash h a) 
Instance details

Defined in Cardano.Crypto.Hash.Class

Associated Types

type Rep (Hash h a) ∷ TypeType Source #

Methods

fromHash h a → Rep (Hash h a) x Source #

toRep (Hash h a) x → Hash h a Source #

Generic (Cofree f a) 
Instance details

Defined in Control.Comonad.Cofree

Associated Types

type Rep (Cofree f a) ∷ TypeType Source #

Methods

fromCofree f a → Rep (Cofree f a) x Source #

toRep (Cofree f a) x → Cofree f a Source #

Generic (Free f a) 
Instance details

Defined in Control.Monad.Free

Associated Types

type Rep (Free f a) ∷ TypeType Source #

Methods

fromFree f a → Rep (Free f a) x Source #

toRep (Free f a) x → Free f a Source #

Generic (ListT m a) 
Instance details

Defined in ListT

Associated Types

type Rep (ListT m a) ∷ TypeType Source #

Methods

from ∷ ListT m a → Rep (ListT m a) x Source #

toRep (ListT m a) x → ListT m a Source #

Generic (ParseError s e) 
Instance details

Defined in Text.Megaparsec.Error

Associated Types

type Rep (ParseError s e) ∷ TypeType Source #

Methods

fromParseError s e → Rep (ParseError s e) x Source #

toRep (ParseError s e) x → ParseError s e Source #

Generic (ParseErrorBundle s e) 
Instance details

Defined in Text.Megaparsec.Error

Associated Types

type Rep (ParseErrorBundle s e) ∷ TypeType Source #

Generic (State s e) 
Instance details

Defined in Text.Megaparsec.State

Associated Types

type Rep (State s e) ∷ TypeType Source #

Methods

fromState s e → Rep (State s e) x Source #

toRep (State s e) x → State s e Source #

Generic (TyVarDecl tyname ann) Source # 
Instance details

Defined in PlutusCore.Core.Type

Associated Types

type Rep (TyVarDecl tyname ann) ∷ TypeType Source #

Methods

fromTyVarDecl tyname ann → Rep (TyVarDecl tyname ann) x Source #

toRep (TyVarDecl tyname ann) x → TyVarDecl tyname ann Source #

Generic (EvaluationError structural operational) Source # 
Instance details

Defined in PlutusCore.Evaluation.Error

Associated Types

type Rep (EvaluationError structural operational) ∷ TypeType Source #

Methods

fromEvaluationError structural operational → Rep (EvaluationError structural operational) x Source #

toRep (EvaluationError structural operational) x → EvaluationError structural operational Source #

Generic (ErrorWithCause err cause) Source # 
Instance details

Defined in PlutusCore.Evaluation.ErrorWithCause

Associated Types

type Rep (ErrorWithCause err cause) ∷ TypeType Source #

Methods

fromErrorWithCause err cause → Rep (ErrorWithCause err cause) x Source #

toRep (ErrorWithCause err cause) x → ErrorWithCause err cause Source #

Generic (Def var val) Source # 
Instance details

Defined in PlutusCore.MkPlc

Associated Types

type Rep (Def var val) ∷ TypeType Source #

Methods

fromDef var val → Rep (Def var val) x Source #

toRep (Def var val) x → Def var val Source #

Generic (UVarDecl name ann) Source # 
Instance details

Defined in UntypedPlutusCore.Core.Type

Associated Types

type Rep (UVarDecl name ann) ∷ TypeType Source #

Methods

fromUVarDecl name ann → Rep (UVarDecl name ann) x Source #

toRep (UVarDecl name ann) x → UVarDecl name ann Source #

Generic (ListF a b) 
Instance details

Defined in Data.Functor.Base

Associated Types

type Rep (ListF a b) ∷ TypeType Source #

Methods

fromListF a b → Rep (ListF a b) x Source #

toRep (ListF a b) x → ListF a b Source #

Generic (NonEmptyF a b) 
Instance details

Defined in Data.Functor.Base

Associated Types

type Rep (NonEmptyF a b) ∷ TypeType Source #

Methods

fromNonEmptyF a b → Rep (NonEmptyF a b) x Source #

toRep (NonEmptyF a b) x → NonEmptyF a b Source #

Generic (TreeF a b) 
Instance details

Defined in Data.Functor.Base

Associated Types

type Rep (TreeF a b) ∷ TypeType Source #

Methods

fromTreeF a b → Rep (TreeF a b) x Source #

toRep (TreeF a b) x → TreeF a b Source #

Generic (Either a b) 
Instance details

Defined in Data.Strict.Either

Associated Types

type Rep (Either a b) ∷ TypeType Source #

Methods

from ∷ Either a b → Rep (Either a b) x Source #

toRep (Either a b) x → Either a b Source #

Generic (These a b) 
Instance details

Defined in Data.Strict.These

Associated Types

type Rep (These a b) ∷ TypeType Source #

Methods

from ∷ These a b → Rep (These a b) x Source #

toRep (These a b) x → These a b Source #

Generic (Pair a b) 
Instance details

Defined in Data.Strict.Tuple

Associated Types

type Rep (Pair a b) ∷ TypeType Source #

Methods

from ∷ Pair a b → Rep (Pair a b) x Source #

toRep (Pair a b) x → Pair a b Source #

Generic (These a b) 
Instance details

Defined in Data.These

Associated Types

type Rep (These a b) ∷ TypeType Source #

Methods

fromThese a b → Rep (These a b) x Source #

toRep (These a b) x → These a b Source #

Generic (Lift f a) 
Instance details

Defined in Control.Applicative.Lift

Associated Types

type Rep (Lift f a) ∷ TypeType Source #

Methods

fromLift f a → Rep (Lift f a) x Source #

toRep (Lift f a) x → Lift f a Source #

Generic (MaybeT m a) 
Instance details

Defined in Control.Monad.Trans.Maybe

Associated Types

type Rep (MaybeT m a) ∷ TypeType Source #

Methods

fromMaybeT m a → Rep (MaybeT m a) x Source #

toRep (MaybeT m a) x → MaybeT m a Source #

Generic (a, b) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b) ∷ TypeType Source #

Methods

from ∷ (a, b) → Rep (a, b) x Source #

toRep (a, b) x → (a, b) Source #

Generic (WrappedArrow a b c) 
Instance details

Defined in Control.Applicative

Associated Types

type Rep (WrappedArrow a b c) ∷ TypeType Source #

Methods

fromWrappedArrow a b c → Rep (WrappedArrow a b c) x Source #

toRep (WrappedArrow a b c) x → WrappedArrow a b c Source #

Generic (Kleisli m a b) 
Instance details

Defined in Control.Arrow

Associated Types

type Rep (Kleisli m a b) ∷ TypeType Source #

Methods

fromKleisli m a b → Rep (Kleisli m a b) x Source #

toRep (Kleisli m a b) x → Kleisli m a b Source #

Generic (Const a b) 
Instance details

Defined in Data.Functor.Const

Associated Types

type Rep (Const a b) ∷ TypeType Source #

Methods

fromConst a b → Rep (Const a b) x Source #

toRep (Const a b) x → Const a b Source #

Generic (Ap f a) 
Instance details

Defined in Data.Monoid

Associated Types

type Rep (Ap f a) ∷ TypeType Source #

Methods

fromAp f a → Rep (Ap f a) x Source #

toRep (Ap f a) x → Ap f a Source #

Generic (Alt f a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Alt f a) ∷ TypeType Source #

Methods

fromAlt f a → Rep (Alt f a) x Source #

toRep (Alt f a) x → Alt f a Source #

Generic (Rec1 f p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Rec1 f p) ∷ TypeType Source #

Methods

fromRec1 f p → Rep (Rec1 f p) x Source #

toRep (Rec1 f p) x → Rec1 f p Source #

Generic (URec (Ptr ()) p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec (Ptr ()) p) ∷ TypeType Source #

Methods

fromURec (Ptr ()) p → Rep (URec (Ptr ()) p) x Source #

toRep (URec (Ptr ()) p) x → URec (Ptr ()) p Source #

Generic (URec Char p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Char p) ∷ TypeType Source #

Methods

fromURec Char p → Rep (URec Char p) x Source #

toRep (URec Char p) x → URec Char p Source #

Generic (URec Double p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Double p) ∷ TypeType Source #

Methods

fromURec Double p → Rep (URec Double p) x Source #

toRep (URec Double p) x → URec Double p Source #

Generic (URec Float p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Float p) ∷ TypeType Source #

Methods

fromURec Float p → Rep (URec Float p) x Source #

toRep (URec Float p) x → URec Float p Source #

Generic (URec Int p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Int p) ∷ TypeType Source #

Methods

fromURec Int p → Rep (URec Int p) x Source #

toRep (URec Int p) x → URec Int p Source #

Generic (URec Word p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Word p) ∷ TypeType Source #

Methods

fromURec Word p → Rep (URec Word p) x Source #

toRep (URec Word p) x → URec Word p Source #

Generic (Fix p a) 
Instance details

Defined in Data.Bifunctor.Fix

Associated Types

type Rep (Fix p a) ∷ TypeType Source #

Methods

fromFix p a → Rep (Fix p a) x Source #

toRep (Fix p a) x → Fix p a Source #

Generic (Join p a) 
Instance details

Defined in Data.Bifunctor.Join

Associated Types

type Rep (Join p a) ∷ TypeType Source #

Methods

fromJoin p a → Rep (Join p a) x Source #

toRep (Join p a) x → Join p a Source #

Generic (CofreeF f a b) 
Instance details

Defined in Control.Comonad.Trans.Cofree

Associated Types

type Rep (CofreeF f a b) ∷ TypeType Source #

Methods

fromCofreeF f a b → Rep (CofreeF f a b) x Source #

toRep (CofreeF f a b) x → CofreeF f a b Source #

Generic (FreeF f a b) 
Instance details

Defined in Control.Monad.Trans.Free

Associated Types

type Rep (FreeF f a b) ∷ TypeType Source #

Methods

fromFreeF f a b → Rep (FreeF f a b) x Source #

toRep (FreeF f a b) x → FreeF f a b Source #

Generic (TyDecl tyname uni ann) Source # 
Instance details

Defined in PlutusCore.Core.Type

Associated Types

type Rep (TyDecl tyname uni ann) ∷ TypeType Source #

Methods

fromTyDecl tyname uni ann → Rep (TyDecl tyname uni ann) x Source #

toRep (TyDecl tyname uni ann) x → TyDecl tyname uni ann Source #

Generic (Type tyname uni ann) Source # 
Instance details

Defined in PlutusCore.Core.Type

Associated Types

type Rep (Type tyname uni ann) ∷ TypeType Source #

Methods

fromType tyname uni ann → Rep (Type tyname uni ann) x Source #

toRep (Type tyname uni ann) x → Type tyname uni ann Source #

Generic (Error uni fun ann) Source # 
Instance details

Defined in PlutusCore.Error

Associated Types

type Rep (Error uni fun ann) ∷ TypeType Source #

Methods

fromError uni fun ann → Rep (Error uni fun ann) x Source #

toRep (Error uni fun ann) x → Error uni fun ann Source #

Generic (MachineParameters machinecosts fun val) Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.MachineParameters

Associated Types

type Rep (MachineParameters machinecosts fun val) ∷ TypeType Source #

Methods

fromMachineParameters machinecosts fun val → Rep (MachineParameters machinecosts fun val) x Source #

toRep (MachineParameters machinecosts fun val) x → MachineParameters machinecosts fun val Source #

Generic (Tagged s b) 
Instance details

Defined in Data.Tagged

Associated Types

type Rep (Tagged s b) ∷ TypeType Source #

Methods

fromTagged s b → Rep (Tagged s b) x Source #

toRep (Tagged s b) x → Tagged s b Source #

Generic (These1 f g a) 
Instance details

Defined in Data.Functor.These

Associated Types

type Rep (These1 f g a) ∷ TypeType Source #

Methods

fromThese1 f g a → Rep (These1 f g a) x Source #

toRep (These1 f g a) x → These1 f g a Source #

Generic (Backwards f a) 
Instance details

Defined in Control.Applicative.Backwards

Associated Types

type Rep (Backwards f a) ∷ TypeType Source #

Methods

fromBackwards f a → Rep (Backwards f a) x Source #

toRep (Backwards f a) x → Backwards f a Source #

Generic (AccumT w m a) 
Instance details

Defined in Control.Monad.Trans.Accum

Associated Types

type Rep (AccumT w m a) ∷ TypeType Source #

Methods

fromAccumT w m a → Rep (AccumT w m a) x Source #

toRep (AccumT w m a) x → AccumT w m a Source #

Generic (ExceptT e m a) 
Instance details

Defined in Control.Monad.Trans.Except

Associated Types

type Rep (ExceptT e m a) ∷ TypeType Source #

Methods

fromExceptT e m a → Rep (ExceptT e m a) x Source #

toRep (ExceptT e m a) x → ExceptT e m a Source #

Generic (IdentityT f a) 
Instance details

Defined in Control.Monad.Trans.Identity

Associated Types

type Rep (IdentityT f a) ∷ TypeType Source #

Methods

fromIdentityT f a → Rep (IdentityT f a) x Source #

toRep (IdentityT f a) x → IdentityT f a Source #

Generic (ReaderT r m a) 
Instance details

Defined in Control.Monad.Trans.Reader

Associated Types

type Rep (ReaderT r m a) ∷ TypeType Source #

Methods

fromReaderT r m a → Rep (ReaderT r m a) x Source #

toRep (ReaderT r m a) x → ReaderT r m a Source #

Generic (SelectT r m a) 
Instance details

Defined in Control.Monad.Trans.Select

Associated Types

type Rep (SelectT r m a) ∷ TypeType Source #

Methods

fromSelectT r m a → Rep (SelectT r m a) x Source #

toRep (SelectT r m a) x → SelectT r m a Source #

Generic (StateT s m a) 
Instance details

Defined in Control.Monad.Trans.State.Lazy

Associated Types

type Rep (StateT s m a) ∷ TypeType Source #

Methods

fromStateT s m a → Rep (StateT s m a) x Source #

toRep (StateT s m a) x → StateT s m a Source #

Generic (StateT s m a) 
Instance details

Defined in Control.Monad.Trans.State.Strict

Associated Types

type Rep (StateT s m a) ∷ TypeType Source #

Methods

fromStateT s m a → Rep (StateT s m a) x Source #

toRep (StateT s m a) x → StateT s m a Source #

Generic (WriterT w m a) 
Instance details

Defined in Control.Monad.Trans.Writer.CPS

Associated Types

type Rep (WriterT w m a) ∷ TypeType Source #

Methods

fromWriterT w m a → Rep (WriterT w m a) x Source #

toRep (WriterT w m a) x → WriterT w m a Source #

Generic (WriterT w m a) 
Instance details

Defined in Control.Monad.Trans.Writer.Lazy

Associated Types

type Rep (WriterT w m a) ∷ TypeType Source #

Methods

fromWriterT w m a → Rep (WriterT w m a) x Source #

toRep (WriterT w m a) x → WriterT w m a Source #

Generic (WriterT w m a) 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

Associated Types

type Rep (WriterT w m a) ∷ TypeType Source #

Methods

fromWriterT w m a → Rep (WriterT w m a) x Source #

toRep (WriterT w m a) x → WriterT w m a Source #

Generic (Constant a b) 
Instance details

Defined in Data.Functor.Constant

Associated Types

type Rep (Constant a b) ∷ TypeType Source #

Methods

fromConstant a b → Rep (Constant a b) x Source #

toRep (Constant a b) x → Constant a b Source #

Generic (Reverse f a) 
Instance details

Defined in Data.Functor.Reverse

Associated Types

type Rep (Reverse f a) ∷ TypeType Source #

Methods

fromReverse f a → Rep (Reverse f a) x Source #

toRep (Reverse f a) x → Reverse f a Source #

Generic (a, b, c) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c) ∷ TypeType Source #

Methods

from ∷ (a, b, c) → Rep (a, b, c) x Source #

toRep (a, b, c) x → (a, b, c) Source #

Generic (Product f g a) 
Instance details

Defined in Data.Functor.Product

Associated Types

type Rep (Product f g a) ∷ TypeType Source #

Methods

fromProduct f g a → Rep (Product f g a) x Source #

toRep (Product f g a) x → Product f g a Source #

Generic (Sum f g a) 
Instance details

Defined in Data.Functor.Sum

Associated Types

type Rep (Sum f g a) ∷ TypeType Source #

Methods

fromSum f g a → Rep (Sum f g a) x Source #

toRep (Sum f g a) x → Sum f g a Source #

Generic ((f :*: g) p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep ((f :*: g) p) ∷ TypeType Source #

Methods

from ∷ (f :*: g) p → Rep ((f :*: g) p) x Source #

toRep ((f :*: g) p) x → (f :*: g) p Source #

Generic ((f :+: g) p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep ((f :+: g) p) ∷ TypeType Source #

Methods

from ∷ (f :+: g) p → Rep ((f :+: g) p) x Source #

toRep ((f :+: g) p) x → (f :+: g) p Source #

Generic (K1 i c p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (K1 i c p) ∷ TypeType Source #

Methods

fromK1 i c p → Rep (K1 i c p) x Source #

toRep (K1 i c p) x → K1 i c p Source #

Generic (VarDecl tyname name uni ann) Source # 
Instance details

Defined in PlutusCore.Core.Type

Associated Types

type Rep (VarDecl tyname name uni ann) ∷ TypeType Source #

Methods

fromVarDecl tyname name uni ann → Rep (VarDecl tyname name uni ann) x Source #

toRep (VarDecl tyname name uni ann) x → VarDecl tyname name uni ann Source #

Generic (TypeError term uni fun ann) Source # 
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 #

Generic (Program name uni fun ann) Source # 
Instance details

Defined in UntypedPlutusCore.Core.Type

Associated Types

type Rep (Program name uni fun ann) ∷ TypeType Source #

Methods

fromProgram name uni fun ann → Rep (Program name uni fun ann) x Source #

toRep (Program name uni fun ann) x → Program name uni fun ann Source #

Generic (Term name uni fun ann) Source # 
Instance details

Defined in UntypedPlutusCore.Core.Type

Associated Types

type Rep (Term name uni fun ann) ∷ TypeType Source #

Methods

fromTerm name uni fun ann → Rep (Term name uni fun ann) x Source #

toRep (Term name uni fun ann) x → Term name uni fun ann Source #

Generic (ContT r m a) 
Instance details

Defined in Control.Monad.Trans.Cont

Associated Types

type Rep (ContT r m a) ∷ TypeType Source #

Methods

fromContT r m a → Rep (ContT r m a) x Source #

toRep (ContT r m a) x → ContT r m a Source #

Generic (a, b, c, d) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d) ∷ TypeType Source #

Methods

from ∷ (a, b, c, d) → Rep (a, b, c, d) x Source #

toRep (a, b, c, d) x → (a, b, c, d) Source #

Generic (Compose f g a) 
Instance details

Defined in Data.Functor.Compose

Associated Types

type Rep (Compose f g a) ∷ TypeType Source #

Methods

fromCompose f g a → Rep (Compose f g a) x Source #

toRep (Compose f g a) x → Compose f g a Source #

Generic ((f :.: g) p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep ((f :.: g) p) ∷ TypeType Source #

Methods

from ∷ (f :.: g) p → Rep ((f :.: g) p) x Source #

toRep ((f :.: g) p) x → (f :.: g) p Source #

Generic (M1 i c f p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (M1 i c f p) ∷ TypeType Source #

Methods

fromM1 i c f p → Rep (M1 i c f p) x Source #

toRep (M1 i c f p) x → M1 i c f p Source #

Generic (Clown f a b) 
Instance details

Defined in Data.Bifunctor.Clown

Associated Types

type Rep (Clown f a b) ∷ TypeType Source #

Methods

fromClown f a b → Rep (Clown f a b) x Source #

toRep (Clown f a b) x → Clown f a b Source #

Generic (Flip p a b) 
Instance details

Defined in Data.Bifunctor.Flip

Associated Types

type Rep (Flip p a b) ∷ TypeType Source #

Methods

fromFlip p a b → Rep (Flip p a b) x Source #

toRep (Flip p a b) x → Flip p a b Source #

Generic (Joker g a b) 
Instance details

Defined in Data.Bifunctor.Joker

Associated Types

type Rep (Joker g a b) ∷ TypeType Source #

Methods

fromJoker g a b → Rep (Joker g a b) x Source #

toRep (Joker g a b) x → Joker g a b Source #

Generic (WrappedBifunctor p a b) 
Instance details

Defined in Data.Bifunctor.Wrapped

Associated Types

type Rep (WrappedBifunctor p a b) ∷ TypeType Source #

Methods

fromWrappedBifunctor p a b → Rep (WrappedBifunctor p a b) x Source #

toRep (WrappedBifunctor p a b) x → WrappedBifunctor p a b Source #

Generic (Program tyname name uni fun ann) Source # 
Instance details

Defined in PlutusCore.Core.Type

Associated Types

type Rep (Program tyname name uni fun ann) ∷ TypeType Source #

Methods

fromProgram tyname name uni fun ann → Rep (Program tyname name uni fun ann) x Source #

toRep (Program tyname name uni fun ann) x → Program tyname name uni fun ann Source #

Generic (Term tyname name uni fun ann) Source # 
Instance details

Defined in PlutusCore.Core.Type

Associated Types

type Rep (Term tyname name uni fun ann) ∷ TypeType Source #

Methods

fromTerm tyname name uni fun ann → Rep (Term tyname name uni fun ann) x Source #

toRep (Term tyname name uni fun ann) x → Term tyname name uni fun ann Source #

Generic (NormCheckError tyname name uni fun ann) Source # 
Instance details

Defined in PlutusCore.Error

Associated Types

type Rep (NormCheckError tyname name uni fun ann) ∷ TypeType Source #

Methods

fromNormCheckError tyname name uni fun ann → Rep (NormCheckError tyname name uni fun ann) x Source #

toRep (NormCheckError tyname name uni fun ann) x → NormCheckError tyname name uni fun ann Source #

Generic (RWST r w s m a) 
Instance details

Defined in Control.Monad.Trans.RWS.CPS

Associated Types

type Rep (RWST r w s m a) ∷ TypeType Source #

Methods

fromRWST r w s m a → Rep (RWST r w s m a) x Source #

toRep (RWST r w s m a) x → RWST r w s m a Source #

Generic (RWST r w s m a) 
Instance details

Defined in Control.Monad.Trans.RWS.Lazy

Associated Types

type Rep (RWST r w s m a) ∷ TypeType Source #

Methods

fromRWST r w s m a → Rep (RWST r w s m a) x Source #

toRep (RWST r w s m a) x → RWST r w s m a Source #

Generic (RWST r w s m a) 
Instance details

Defined in Control.Monad.Trans.RWS.Strict

Associated Types

type Rep (RWST r w s m a) ∷ TypeType Source #

Methods

fromRWST r w s m a → Rep (RWST r w s m a) x Source #

toRep (RWST r w s m a) x → RWST r w s m a Source #

Generic (a, b, c, d, e) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e) ∷ TypeType Source #

Methods

from ∷ (a, b, c, d, e) → Rep (a, b, c, d, e) x Source #

toRep (a, b, c, d, e) x → (a, b, c, d, e) Source #

Generic (Product f g a b) 
Instance details

Defined in Data.Bifunctor.Product

Associated Types

type Rep (Product f g a b) ∷ TypeType Source #

Methods

fromProduct f g a b → Rep (Product f g a b) x Source #

toRep (Product f g a b) x → Product f g a b Source #

Generic (Sum p q a b) 
Instance details

Defined in Data.Bifunctor.Sum

Associated Types

type Rep (Sum p q a b) ∷ TypeType Source #

Methods

fromSum p q a b → Rep (Sum p q a b) x Source #

toRep (Sum p q a b) x → Sum p q a b Source #

Generic (a, b, c, d, e, f) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f) ∷ TypeType Source #

Methods

from ∷ (a, b, c, d, e, f) → Rep (a, b, c, d, e, f) x Source #

toRep (a, b, c, d, e, f) x → (a, b, c, d, e, f) Source #

Generic (Tannen f p a b) 
Instance details

Defined in Data.Bifunctor.Tannen

Associated Types

type Rep (Tannen f p a b) ∷ TypeType Source #

Methods

fromTannen f p a b → Rep (Tannen f p a b) x Source #

toRep (Tannen f p a b) x → Tannen f p a b Source #

Generic (a, b, c, d, e, f, g) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g) ∷ TypeType Source #

Methods

from ∷ (a, b, c, d, e, f, g) → Rep (a, b, c, d, e, f, g) x Source #

toRep (a, b, c, d, e, f, g) x → (a, b, c, d, e, f, g) Source #

Generic (a, b, c, d, e, f, g, h) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g, h) ∷ TypeType Source #

Methods

from ∷ (a, b, c, d, e, f, g, h) → Rep (a, b, c, d, e, f, g, h) x Source #

toRep (a, b, c, d, e, f, g, h) x → (a, b, c, d, e, f, g, h) Source #

Generic (Biff p f g a b) 
Instance details

Defined in Data.Bifunctor.Biff

Associated Types

type Rep (Biff p f g a b) ∷ TypeType Source #

Methods

fromBiff p f g a b → Rep (Biff p f g a b) x Source #

toRep (Biff p f g a b) x → Biff p f g a b Source #

Generic (a, b, c, d, e, f, g, h, i) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g, h, i) ∷ TypeType Source #

Methods

from ∷ (a, b, c, d, e, f, g, h, i) → Rep (a, b, c, d, e, f, g, h, i) x Source #

toRep (a, b, c, d, e, f, g, h, i) x → (a, b, c, d, e, f, g, h, i) Source #

Generic (a, b, c, d, e, f, g, h, i, j) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j) ∷ TypeType Source #

Methods

from ∷ (a, b, c, d, e, f, g, h, i, j) → Rep (a, b, c, d, e, f, g, h, i, j) x Source #

toRep (a, b, c, d, e, f, g, h, i, j) x → (a, b, c, d, e, f, g, h, i, j) Source #

Generic (a, b, c, d, e, f, g, h, i, j, k) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j, k) ∷ TypeType Source #

Methods

from ∷ (a, b, c, d, e, f, g, h, i, j, k) → Rep (a, b, c, d, e, f, g, h, i, j, k) x Source #

toRep (a, b, c, d, e, f, g, h, i, j, k) x → (a, b, c, d, e, f, g, h, i, j, k) Source #

Generic (a, b, c, d, e, f, g, h, i, j, k, l) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j, k, l) ∷ TypeType Source #

Methods

from ∷ (a, b, c, d, e, f, g, h, i, j, k, l) → Rep (a, b, c, d, e, f, g, h, i, j, k, l) x Source #

toRep (a, b, c, d, e, f, g, h, i, j, k, l) x → (a, b, c, d, e, f, g, h, i, j, k, l) Source #

Generic (a, b, c, d, e, f, g, h, i, j, k, l, m) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j, k, l, m) ∷ TypeType Source #

Methods

from ∷ (a, b, c, d, e, f, g, h, i, j, k, l, m) → Rep (a, b, c, d, e, f, g, h, i, j, k, l, m) x Source #

toRep (a, b, c, d, e, f, g, h, i, j, k, l, m) x → (a, b, c, d, e, f, g, h, i, j, k, l, m) Source #

Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n) ∷ TypeType Source #

Methods

from ∷ (a, b, c, d, e, f, g, h, i, j, k, l, m, n) → Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n) x Source #

toRep (a, b, c, d, e, f, g, h, i, j, k, l, m, n) x → (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source #

Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) ∷ TypeType Source #

Methods

from ∷ (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) → Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) x Source #

toRep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) x → (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source #

class NFData a Source #

A class of types that can be fully evaluated.

Since: deepseq-1.1.0.0

Instances

Instances details
NFData Key 
Instance details

Defined in Data.Aeson.Key

Methods

rnf ∷ Key → () Source #

NFData JSONPathElement 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

rnf ∷ JSONPathElement → () Source #

NFData Value 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

rnf ∷ Value → () Source #

NFData ByteArray

Since: deepseq-1.4.7.0

Instance details

Defined in Control.DeepSeq

Methods

rnfByteArray → () Source #

NFData All

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfAll → () Source #

NFData Any

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfAny → () Source #

NFData TypeRep

NOTE: Prior to deepseq-1.4.4.0 this instance was only defined for base-4.8.0.0 and later.

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfTypeRep → () Source #

NFData Unique

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfUnique → () Source #

NFData Version

Since: deepseq-1.3.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfVersion → () Source #

NFData CBool

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

rnfCBool → () Source #

NFData CChar

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfCChar → () Source #

NFData CClock

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfCClock → () Source #

NFData CDouble

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfCDouble → () Source #

NFData CFile

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfCFile → () Source #

NFData CFloat

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfCFloat → () Source #

NFData CFpos

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfCFpos → () Source #

NFData CInt

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfCInt → () Source #

NFData CIntMax

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfCIntMax → () Source #

NFData CIntPtr

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfCIntPtr → () Source #

NFData CJmpBuf

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfCJmpBuf → () Source #

NFData CLLong

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfCLLong → () Source #

NFData CLong

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfCLong → () Source #

NFData CPtrdiff

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfCPtrdiff → () Source #

NFData CSChar

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfCSChar → () Source #

NFData CSUSeconds

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfCSUSeconds → () Source #

NFData CShort

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfCShort → () Source #

NFData CSigAtomic

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfCSigAtomic → () Source #

NFData CSize

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfCSize → () Source #

NFData CTime

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfCTime → () Source #

NFData CUChar

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfCUChar → () Source #

NFData CUInt

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfCUInt → () Source #

NFData CUIntMax

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfCUIntMax → () Source #

NFData CUIntPtr

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfCUIntPtr → () Source #

NFData CULLong

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfCULLong → () Source #

NFData CULong

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfCULong → () Source #

NFData CUSeconds

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfCUSeconds → () Source #

NFData CUShort

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfCUShort → () Source #

NFData CWchar

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfCWchar → () Source #

NFData Void

Defined as rnf = absurd.

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfVoid → () Source #

NFData ThreadId

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfThreadId → () Source #

NFData Fingerprint

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfFingerprint → () Source #

NFData MaskingState

Since: deepseq-1.4.4.0

Instance details

Defined in Control.DeepSeq

Methods

rnfMaskingState → () Source #

NFData ExitCode

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnfExitCode → () Source #

NFData Int16 
Instance details

Defined in Control.DeepSeq

Methods

rnfInt16 → () Source #

NFData Int32 
Instance details

Defined in Control.DeepSeq

Methods

rnfInt32 → () Source #

NFData Int64 
Instance details

Defined in Control.DeepSeq

Methods

rnfInt64 → () Source #

NFData Int8 
Instance details

Defined in Control.DeepSeq

Methods

rnfInt8 → () Source #

NFData CallStack

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnfCallStack → () Source #

NFData SrcLoc

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnfSrcLoc → () Source #

NFData Word16 
Instance details

Defined in Control.DeepSeq

Methods

rnfWord16 → () Source #

NFData Word32 
Instance details

Defined in Control.DeepSeq

Methods

rnfWord32 → () Source #

NFData Word64 
Instance details

Defined in Control.DeepSeq

Methods

rnfWord64 → () Source #

NFData Word8 
Instance details

Defined in Control.DeepSeq

Methods

rnfWord8 → () Source #

NFData ByteString 
Instance details

Defined in Data.ByteString.Internal.Type

Methods

rnfByteString → () Source #

NFData ByteString 
Instance details

Defined in Data.ByteString.Lazy.Internal

Methods

rnfByteString → () Source #

NFData ShortByteString 
Instance details

Defined in Data.ByteString.Short.Internal

Methods

rnfShortByteString → () Source #

NFData PublicKey 
Instance details

Defined in Crypto.ECC.Ed25519Donna

Methods

rnfPublicKey → () Source #

NFData SecretKey 
Instance details

Defined in Crypto.ECC.Ed25519Donna

Methods

rnfSecretKey → () Source #

NFData Signature 
Instance details

Defined in Crypto.ECC.Ed25519Donna

Methods

rnfSignature → () Source #

NFData DeserialiseFailure 
Instance details

Defined in Codec.CBOR.Read

Methods

rnfDeserialiseFailure → () Source #

NFData IntSet 
Instance details

Defined in Data.IntSet.Internal

Methods

rnfIntSet → () Source #

NFData OsChar 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Methods

rnfOsChar → () Source #

NFData OsString 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Methods

rnfOsString → () Source #

NFData PosixChar 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Methods

rnfPosixChar → () Source #

NFData PosixString 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Methods

rnfPosixString → () Source #

NFData WindowsChar 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Methods

rnfWindowsChar → () Source #

NFData WindowsString 
Instance details

Defined in System.OsString.Internal.Types.Hidden

Methods

rnfWindowsString → () Source #

NFData Filler 
Instance details

Defined in Flat.Filler

Methods

rnfFiller → () Source #

NFData Module

Since: deepseq-1.4.8.0

Instance details

Defined in Control.DeepSeq

Methods

rnfModule → () Source #

NFData Ordering 
Instance details

Defined in Control.DeepSeq

Methods

rnfOrdering → () Source #

NFData TyCon

NOTE: Prior to deepseq-1.4.4.0 this instance was only defined for base-4.8.0.0 and later.

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfTyCon → () Source #

NFData Half 
Instance details

Defined in Numeric.Half.Internal

Methods

rnf ∷ Half → () Source #

NFData InvalidPosException 
Instance details

Defined in Text.Megaparsec.Pos

Methods

rnfInvalidPosException → () Source #

NFData Pos 
Instance details

Defined in Text.Megaparsec.Pos

Methods

rnfPos → () Source #

NFData SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Methods

rnfSourcePos → () Source #

NFData URI 
Instance details

Defined in Network.URI

Methods

rnf ∷ URI → () Source #

NFData URIAuth 
Instance details

Defined in Network.URI

Methods

rnf ∷ URIAuth → () Source #

NFData OsChar 
Instance details

Defined in System.OsString.Internal.Types

Methods

rnf ∷ OsChar → () Source #

NFData OsString 
Instance details

Defined in System.OsString.Internal.Types

Methods

rnf ∷ OsString → () Source #

NFData PosixChar 
Instance details

Defined in System.OsString.Internal.Types

Methods

rnf ∷ PosixChar → () Source #

NFData PosixString 
Instance details

Defined in System.OsString.Internal.Types

Methods

rnf ∷ PosixString → () Source #

NFData WindowsChar 
Instance details

Defined in System.OsString.Internal.Types

Methods

rnf ∷ WindowsChar → () Source #

NFData WindowsString 
Instance details

Defined in System.OsString.Internal.Types

Methods

rnf ∷ WindowsString → () Source #

NFData SrcSpan Source # 
Instance details

Defined in PlutusCore.Annotation

Methods

rnfSrcSpan → () Source #

NFData SrcSpans Source # 
Instance details

Defined in PlutusCore.Annotation

Methods

rnfSrcSpans → () Source #

NFData UnliftingError Source # 
Instance details

Defined in PlutusCore.Builtin.Result

Methods

rnfUnliftingError → () Source #

NFData UnliftingEvaluationError Source # 
Instance details

Defined in PlutusCore.Builtin.Result

NFData Element Source # 
Instance details

Defined in PlutusCore.Crypto.BLS12_381.G1

Methods

rnfElement → () Source #

NFData Element Source # 
Instance details

Defined in PlutusCore.Crypto.BLS12_381.G2

Methods

rnfElement → () Source #

NFData MlResult Source # 
Instance details

Defined in PlutusCore.Crypto.BLS12_381.Pairing

Methods

rnfMlResult → () Source #

NFData Data Source # 
Instance details

Defined in PlutusCore.Data

Methods

rnfData → () Source #

NFData DeBruijn Source # 
Instance details

Defined in PlutusCore.DeBruijn.Internal

Methods

rnfDeBruijn → () Source #

NFData FakeNamedDeBruijn Source # 
Instance details

Defined in PlutusCore.DeBruijn.Internal

Methods

rnfFakeNamedDeBruijn → () Source #

NFData FreeVariableError Source # 
Instance details

Defined in PlutusCore.DeBruijn.Internal

Methods

rnfFreeVariableError → () Source #

NFData Index Source # 
Instance details

Defined in PlutusCore.DeBruijn.Internal

Methods

rnfIndex → () Source #

NFData NamedDeBruijn Source # 
Instance details

Defined in PlutusCore.DeBruijn.Internal

Methods

rnfNamedDeBruijn → () Source #

NFData NamedTyDeBruijn Source # 
Instance details

Defined in PlutusCore.DeBruijn.Internal

Methods

rnfNamedTyDeBruijn → () Source #

NFData TyDeBruijn Source # 
Instance details

Defined in PlutusCore.DeBruijn.Internal

Methods

rnfTyDeBruijn → () Source #

NFData DefaultFun Source # 
Instance details

Defined in PlutusCore.Default.Builtins

Methods

rnfDefaultFun → () Source #

NFData ParserError Source # 
Instance details

Defined in PlutusCore.Error

Methods

rnfParserError → () Source #

NFData ParserErrorBundle Source # 
Instance details

Defined in PlutusCore.Error

Methods

rnfParserErrorBundle → () Source #

NFData CostModelApplyError Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostModelInterface

Methods

rnfCostModelApplyError → () Source #

NFData Coefficient0 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

rnfCoefficient0 → () Source #

NFData Coefficient00 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

rnfCoefficient00 → () Source #

NFData Coefficient01 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

rnfCoefficient01 → () Source #

NFData Coefficient02 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

rnfCoefficient02 → () Source #

NFData Coefficient1 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

rnfCoefficient1 → () Source #

NFData Coefficient10 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

rnfCoefficient10 → () Source #

NFData Coefficient11 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

rnfCoefficient11 → () Source #

NFData Coefficient2 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

rnfCoefficient2 → () Source #

NFData Coefficient20 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

rnfCoefficient20 → () Source #

NFData Intercept Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

rnfIntercept → () Source #

NFData ModelConstantOrLinear Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

rnfModelConstantOrLinear → () Source #

NFData ModelConstantOrOneArgument Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

NFData ModelConstantOrTwoArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

NFData ModelFiveArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

rnfModelFiveArguments → () Source #

NFData ModelFourArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

rnfModelFourArguments → () Source #

NFData ModelOneArgument Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

rnfModelOneArgument → () Source #

NFData ModelSixArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

rnfModelSixArguments → () Source #

NFData ModelSubtractedSizes Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

rnfModelSubtractedSizes → () Source #

NFData ModelThreeArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

rnfModelThreeArguments → () Source #

NFData ModelTwoArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

rnfModelTwoArguments → () Source #

NFData OneVariableLinearFunction Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

NFData OneVariableQuadraticFunction Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

NFData Slope Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

rnfSlope → () Source #

NFData TwoVariableLinearFunction Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

NFData TwoVariableQuadraticFunction Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

NFData ExBudget Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

Methods

rnfExBudget → () Source #

NFData ExRestrictingBudget Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

Methods

rnfExRestrictingBudget → () Source #

NFData ExCPU Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Methods

rnfExCPU → () Source #

NFData ExMemory Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Methods

rnfExMemory → () Source #

NFData Name Source # 
Instance details

Defined in PlutusCore.Name.Unique

Methods

rnfName → () Source #

NFData TyName Source # 
Instance details

Defined in PlutusCore.Name.Unique

Methods

rnfTyName → () Source #

NFData Unique Source # 
Instance details

Defined in PlutusCore.Name.Unique

Methods

rnfUnique → () Source #

NFData Version Source # 
Instance details

Defined in PlutusCore.Version

Methods

rnfVersion → () Source #

NFData CountingSt Source # 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

Methods

rnfCountingSt → () Source #

NFData RestrictingSt Source # 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

Methods

rnfRestrictingSt → () Source #

NFData CekUserError Source # 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Methods

rnfCekUserError → () Source #

NFData StepKind Source # 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Methods

rnfStepKind → () Source #

NFData SatInt 
Instance details

Defined in Data.SatInt

Methods

rnfSatInt → () Source #

NFData TextDetails 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

rnfTextDetails → () Source #

NFData Doc 
Instance details

Defined in Text.PrettyPrint.HughesPJ

Methods

rnfDoc → () Source #

NFData StdGen 
Instance details

Defined in System.Random.Internal

Methods

rnfStdGen → () Source #

NFData Scientific 
Instance details

Defined in Data.Scientific

Methods

rnf ∷ Scientific → () Source #

NFData UnicodeException 
Instance details

Defined in Data.Text.Encoding.Error

Methods

rnfUnicodeException → () Source #

NFData ShortText 
Instance details

Defined in Data.Text.Short.Internal

Methods

rnf ∷ ShortText → () Source #

NFData Day 
Instance details

Defined in Data.Time.Calendar.Days

Methods

rnfDay → () Source #

NFData DiffTime 
Instance details

Defined in Data.Time.Clock.Internal.DiffTime

Methods

rnfDiffTime → () Source #

NFData NominalDiffTime 
Instance details

Defined in Data.Time.Clock.Internal.NominalDiffTime

Methods

rnfNominalDiffTime → () Source #

NFData UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

Methods

rnfUTCTime → () Source #

NFData UniversalTime 
Instance details

Defined in Data.Time.Clock.Internal.UniversalTime

Methods

rnfUniversalTime → () Source #

NFData LocalTime 
Instance details

Defined in Data.Time.LocalTime.Internal.LocalTime

Methods

rnfLocalTime → () Source #

NFData ZonedTime 
Instance details

Defined in Data.Time.LocalTime.Internal.ZonedTime

Methods

rnfZonedTime → () Source #

NFData UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

rnf ∷ UUID → () Source #

NFData Integer 
Instance details

Defined in Control.DeepSeq

Methods

rnfInteger → () Source #

NFData Natural

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfNatural → () Source #

NFData () 
Instance details

Defined in Control.DeepSeq

Methods

rnf ∷ () → () Source #

NFData Bool 
Instance details

Defined in Control.DeepSeq

Methods

rnfBool → () Source #

NFData Char 
Instance details

Defined in Control.DeepSeq

Methods

rnfChar → () Source #

NFData Double 
Instance details

Defined in Control.DeepSeq

Methods

rnfDouble → () Source #

NFData Float 
Instance details

Defined in Control.DeepSeq

Methods

rnfFloat → () Source #

NFData Int 
Instance details

Defined in Control.DeepSeq

Methods

rnfInt → () Source #

NFData Word 
Instance details

Defined in Control.DeepSeq

Methods

rnfWord → () Source #

NFData a ⇒ NFData (Only a) 
Instance details

Defined in Data.Tuple.Only

Methods

rnf ∷ Only a → () Source #

NFData v ⇒ NFData (KeyMap v) 
Instance details

Defined in Data.Aeson.KeyMap

Methods

rnf ∷ KeyMap v → () Source #

NFData a ⇒ NFData (IResult a) 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

rnf ∷ IResult a → () Source #

NFData a ⇒ NFData (Result a) 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

rnf ∷ Result a → () Source #

NFData a ⇒ NFData (ZipList a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfZipList a → () Source #

NFData (MutableByteArray s)

Since: deepseq-1.4.8.0

Instance details

Defined in Control.DeepSeq

Methods

rnfMutableByteArray s → () Source #

NFData a ⇒ NFData (Complex a) 
Instance details

Defined in Control.DeepSeq

Methods

rnfComplex a → () Source #

NFData a ⇒ NFData (Identity a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfIdentity a → () Source #

NFData a ⇒ NFData (First a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfFirst a → () Source #

NFData a ⇒ NFData (Last a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfLast a → () Source #

NFData a ⇒ NFData (Down a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfDown a → () Source #

NFData a ⇒ NFData (First a)

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnfFirst a → () Source #

NFData a ⇒ NFData (Last a)

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnfLast a → () Source #

NFData a ⇒ NFData (Max a)

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnfMax a → () Source #

NFData a ⇒ NFData (Min a)

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnfMin a → () Source #

NFData m ⇒ NFData (WrappedMonoid m)

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnfWrappedMonoid m → () Source #

NFData a ⇒ NFData (Dual a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfDual a → () Source #

NFData a ⇒ NFData (Product a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfProduct a → () Source #

NFData a ⇒ NFData (Sum a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfSum a → () Source #

NFData a ⇒ NFData (NonEmpty a)

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnfNonEmpty a → () Source #

NFData (IORef a)

NOTE: Only strict in the reference and not the referenced value.

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnfIORef a → () Source #

NFData (MVar a)

NOTE: Only strict in the reference and not the referenced value.

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnfMVar a → () Source #

NFData (FunPtr a)

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnfFunPtr a → () Source #

NFData (Ptr a)

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnfPtr a → () Source #

NFData a ⇒ NFData (Ratio a) 
Instance details

Defined in Control.DeepSeq

Methods

rnfRatio a → () Source #

NFData (StableName a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfStableName a → () Source #

NFData (SigDSIGN EcdsaSecp256k1DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.EcdsaSecp256k1

NFData (SigDSIGN Ed25519DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Ed25519

Methods

rnfSigDSIGN Ed25519DSIGN → () Source #

NFData (SigDSIGN SchnorrSecp256k1DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.SchnorrSecp256k1

NFData (SignKeyDSIGN EcdsaSecp256k1DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.EcdsaSecp256k1

NFData (SignKeyDSIGN Ed25519DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Ed25519

NFData (SignKeyDSIGN SchnorrSecp256k1DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.SchnorrSecp256k1

NFData (VerKeyDSIGN EcdsaSecp256k1DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.EcdsaSecp256k1

NFData (VerKeyDSIGN Ed25519DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Ed25519

Methods

rnfVerKeyDSIGN Ed25519DSIGN → () Source #

NFData (VerKeyDSIGN SchnorrSecp256k1DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.SchnorrSecp256k1

NFData (PackedBytes n) 
Instance details

Defined in Cardano.Crypto.PackedBytes

Methods

rnfPackedBytes n → () Source #

NFData (PinnedSizedBytes n) 
Instance details

Defined in Cardano.Crypto.PinnedSizedBytes

Methods

rnfPinnedSizedBytes n → () Source #

NFData a ⇒ NFData (IntMap a) 
Instance details

Defined in Data.IntMap.Internal

Methods

rnfIntMap a → () Source #

NFData a ⇒ NFData (Digit a) 
Instance details

Defined in Data.Sequence.Internal

Methods

rnfDigit a → () Source #

NFData a ⇒ NFData (Elem a) 
Instance details

Defined in Data.Sequence.Internal

Methods

rnfElem a → () Source #

NFData a ⇒ NFData (FingerTree a) 
Instance details

Defined in Data.Sequence.Internal

Methods

rnfFingerTree a → () Source #

NFData a ⇒ NFData (Node a) 
Instance details

Defined in Data.Sequence.Internal

Methods

rnfNode a → () Source #

NFData a ⇒ NFData (Seq a) 
Instance details

Defined in Data.Sequence.Internal

Methods

rnfSeq a → () Source #

NFData a ⇒ NFData (Set a) 
Instance details

Defined in Data.Set.Internal

Methods

rnfSet a → () Source #

NFData a ⇒ NFData (Tree a) 
Instance details

Defined in Data.Tree

Methods

rnfTree a → () Source #

NFData (Context a) 
Instance details

Defined in Crypto.Hash.Types

Methods

rnfContext a → () Source #

NFData (Digest a) 
Instance details

Defined in Crypto.Hash.Types

Methods

rnfDigest a → () Source #

NFData1 f ⇒ NFData (Fix f) 
Instance details

Defined in Data.Fix

Methods

rnf ∷ Fix f → () Source #

NFData a ⇒ NFData (DNonEmpty a) 
Instance details

Defined in Data.DList.DNonEmpty.Internal

Methods

rnfDNonEmpty a → () Source #

NFData a ⇒ NFData (DList a) 
Instance details

Defined in Data.DList.Internal

Methods

rnfDList a → () Source #

NFData (Get a) 
Instance details

Defined in Flat.Decoder.Types

Methods

rnfGet a → () Source #

NFData a ⇒ NFData (PostAligned a) 
Instance details

Defined in Flat.Filler

Methods

rnfPostAligned a → () Source #

NFData a ⇒ NFData (PreAligned a) 
Instance details

Defined in Flat.Filler

Methods

rnfPreAligned a → () Source #

NFData a ⇒ NFData (Hashed a) 
Instance details

Defined in Data.Hashable.Class

Methods

rnfHashed a → () Source #

NFData a ⇒ NFData (ErrorFancy a) 
Instance details

Defined in Text.Megaparsec.Error

Methods

rnfErrorFancy a → () Source #

NFData t ⇒ NFData (ErrorItem t) 
Instance details

Defined in Text.Megaparsec.Error

Methods

rnfErrorItem t → () Source #

NFData s ⇒ NFData (PosState s) 
Instance details

Defined in Text.Megaparsec.State

Methods

rnfPosState s → () Source #

NFData a ⇒ NFData (MultiSet a) 
Instance details

Defined in Data.MultiSet

Methods

rnfMultiSet a → () Source #

NFData (BuiltinSemanticsVariant DefaultFun) Source # 
Instance details

Defined in PlutusCore.Default.Builtins

NFData (BuiltinRuntime val) Source # 
Instance details

Defined in PlutusCore.Builtin.Runtime

Methods

rnfBuiltinRuntime val → () Source #

NFData ann ⇒ NFData (Kind ann) Source # 
Instance details

Defined in PlutusCore.Core.Type

Methods

rnfKind ann → () Source #

NFData a ⇒ NFData (Normalized a) Source # 
Instance details

Defined in PlutusCore.Core.Type

Methods

rnfNormalized a → () Source #

NFData a ⇒ NFData (ExpectedShapeOr a) Source # 
Instance details

Defined in PlutusCore.Error

Methods

rnfExpectedShapeOr a → () Source #

NFData ann ⇒ NFData (UniqueError ann) Source # 
Instance details

Defined in PlutusCore.Error

Methods

rnfUniqueError ann → () Source #

AllArgumentModels NFData f ⇒ NFData (BuiltinCostModelBase f) Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

Methods

rnfBuiltinCostModelBase f → () Source #

NFData model ⇒ NFData (CostingFun model) Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

rnfCostingFun model → () Source #

NFData (MachineError fun) Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

Methods

rnfMachineError fun → () Source #

NFData a ⇒ NFData (EvaluationResult a) Source # 
Instance details

Defined in PlutusCore.Evaluation.Result

Methods

rnfEvaluationResult a → () Source #

Closed uni ⇒ NFData (SomeTypeIn uni) Source # 
Instance details

Defined in Universe.Core

Methods

rnfSomeTypeIn uni → () Source #

AllBF NFData f CekMachineCostsBaseNFData (CekMachineCostsBase f) Source # 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.CekMachineCosts

Methods

rnfCekMachineCostsBase f → () Source #

NFData fun ⇒ NFData (CekExTally fun) Source # 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

Methods

rnfCekExTally fun → () Source #

NFData fun ⇒ NFData (TallyingSt fun) Source # 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

Methods

rnfTallyingSt fun → () Source #

NFData fun ⇒ NFData (ExBudgetCategory fun) Source # 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Methods

rnfExBudgetCategory fun → () Source #

NFData a ⇒ NFData (AnnotDetails a) 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

rnfAnnotDetails a → () Source #

NFData a ⇒ NFData (Doc a) 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

rnfDoc a → () Source #

NFData a ⇒ NFData (Array a) 
Instance details

Defined in Data.Primitive.Array

Methods

rnfArray a → () Source #

NFData (PrimArray a) 
Instance details

Defined in Data.Primitive.PrimArray

Methods

rnfPrimArray a → () Source #

NFData a ⇒ NFData (SmallArray a) 
Instance details

Defined in Data.Primitive.SmallArray

Methods

rnfSmallArray a → () Source #

NFData a ⇒ NFData (Leaf a) 
Instance details

Defined in Data.RAList.Tree.Internal

Methods

rnfLeaf a → () Source #

NFData g ⇒ NFData (StateGen g) 
Instance details

Defined in System.Random.Internal

Methods

rnfStateGen g → () Source #

NFData g ⇒ NFData (AtomicGen g) 
Instance details

Defined in System.Random.Stateful

Methods

rnfAtomicGen g → () Source #

NFData g ⇒ NFData (IOGen g) 
Instance details

Defined in System.Random.Stateful

Methods

rnfIOGen g → () Source #

NFData g ⇒ NFData (STGen g) 
Instance details

Defined in System.Random.Stateful

Methods

rnfSTGen g → () Source #

NFData g ⇒ NFData (TGen g) 
Instance details

Defined in System.Random.Stateful

Methods

rnfTGen g → () Source #

NFData a ⇒ NFData (Maybe a) 
Instance details

Defined in Data.Strict.Maybe

Methods

rnf ∷ Maybe a → () Source #

NFData a ⇒ NFData (Array a) 
Instance details

Defined in Data.HashMap.Internal.Array

Methods

rnfArray a → () Source #

NFData a ⇒ NFData (HashSet a) 
Instance details

Defined in Data.HashSet.Internal

Methods

rnfHashSet a → () Source #

NFData a ⇒ NFData (Vector a) 
Instance details

Defined in Data.Vector

Methods

rnfVector a → () Source #

NFData (Vector a) 
Instance details

Defined in Data.Vector.Primitive

Methods

rnfVector a → () Source #

NFData (Vector a) 
Instance details

Defined in Data.Vector.Storable

Methods

rnfVector a → () Source #

NFData (Vector a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

rnfVector a → () Source #

NFData a ⇒ NFData (Doc a) 
Instance details

Defined in Text.PrettyPrint.Annotated.WL

Methods

rnf ∷ Doc a → () Source #

NFData a ⇒ NFData (SimpleDoc a) 
Instance details

Defined in Text.PrettyPrint.Annotated.WL

Methods

rnf ∷ SimpleDoc a → () Source #

NFData a ⇒ NFData (Maybe a) 
Instance details

Defined in Control.DeepSeq

Methods

rnfMaybe a → () Source #

NFData a ⇒ NFData (a)

Since: deepseq-1.4.6.0

Instance details

Defined in Control.DeepSeq

Methods

rnf ∷ (a) → () Source #

NFData a ⇒ NFData [a] 
Instance details

Defined in Control.DeepSeq

Methods

rnf ∷ [a] → () Source #

(NFData i, NFData r) ⇒ NFData (IResult i r) 
Instance details

Defined in Data.Attoparsec.Internal.Types

Methods

rnf ∷ IResult i r → () Source #

(NFData a, NFData b) ⇒ NFData (Either a b) 
Instance details

Defined in Control.DeepSeq

Methods

rnfEither a b → () Source #

NFData (Fixed a)

Since: deepseq-1.3.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfFixed a → () Source #

NFData (Proxy a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfProxy a → () Source #

(NFData a, NFData b) ⇒ NFData (Arg a b)

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnfArg a b → () Source #

NFData (TypeRep a)

Since: deepseq-1.4.8.0

Instance details

Defined in Control.DeepSeq

Methods

rnfTypeRep a → () Source #

(NFData a, NFData b) ⇒ NFData (Array a b) 
Instance details

Defined in Control.DeepSeq

Methods

rnfArray a b → () Source #

NFData (STRef s a)

NOTE: Only strict in the reference and not the referenced value.

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnfSTRef s a → () Source #

(NFData a, NFData b) ⇒ NFData (Bimap a b) 
Instance details

Defined in Data.Bimap

Methods

rnf ∷ Bimap a b → () Source #

NFData (SigDSIGN v) ⇒ NFData (SignedDSIGN v a) 
Instance details

Defined in Cardano.Crypto.DSIGN.Class

Methods

rnfSignedDSIGN v a → () Source #

NFData (Hash h a) 
Instance details

Defined in Cardano.Crypto.Hash.Class

Methods

rnfHash h a → () Source #

(NFData k, NFData a) ⇒ NFData (Map k a) 
Instance details

Defined in Data.Map.Internal

Methods

rnfMap k a → () Source #

(NFData (Token s), NFData e) ⇒ NFData (ParseError s e) 
Instance details

Defined in Text.Megaparsec.Error

Methods

rnfParseError s e → () Source #

(NFData s, NFData (Token s), NFData e) ⇒ NFData (ParseErrorBundle s e) 
Instance details

Defined in Text.Megaparsec.Error

Methods

rnfParseErrorBundle s e → () Source #

(NFData s, NFData (ParseError s e)) ⇒ NFData (State s e) 
Instance details

Defined in Text.Megaparsec.State

Methods

rnfState s e → () Source #

(NFData k, NFData a) ⇒ NFData (MonoidalHashMap k a) 
Instance details

Defined in Data.HashMap.Monoidal

Methods

rnfMonoidalHashMap k a → () Source #

(Bounded fun, Enum fun) ⇒ NFData (BuiltinsRuntime fun val) Source # 
Instance details

Defined in PlutusCore.Builtin.Runtime

Methods

rnfBuiltinsRuntime fun val → () Source #

(NFData structural, NFData operational) ⇒ NFData (EvaluationError structural operational) Source # 
Instance details

Defined in PlutusCore.Evaluation.Error

Methods

rnfEvaluationError structural operational → () Source #

(NFData err, NFData cause) ⇒ NFData (ErrorWithCause err cause) Source # 
Instance details

Defined in PlutusCore.Evaluation.ErrorWithCause

Methods

rnfErrorWithCause err cause → () Source #

(Closed uni, Everywhere uni NFData) ⇒ NFData (ValueOf uni a) Source # 
Instance details

Defined in Universe.Core

Methods

rnfValueOf uni a → () Source #

NFData (MutablePrimArray s a) 
Instance details

Defined in Data.Primitive.PrimArray

Methods

rnfMutablePrimArray s a → () Source #

NFData (f a) ⇒ NFData (Node f a) 
Instance details

Defined in Data.RAList.Tree.Internal

Methods

rnfNode f a → () Source #

GNFData tag ⇒ NFData (Some tag) 
Instance details

Defined in Data.Some.GADT

Methods

rnfSome tag → () Source #

GNFData tag ⇒ NFData (Some tag) 
Instance details

Defined in Data.Some.Newtype

Methods

rnfSome tag → () Source #

(NFData a, NFData b) ⇒ NFData (Either a b) 
Instance details

Defined in Data.Strict.Either

Methods

rnf ∷ Either a b → () Source #

(NFData a, NFData b) ⇒ NFData (These a b) 
Instance details

Defined in Data.Strict.These

Methods

rnf ∷ These a b → () Source #

(NFData a, NFData b) ⇒ NFData (Pair a b) 
Instance details

Defined in Data.Strict.Tuple

Methods

rnf ∷ Pair a b → () Source #

(NFData a, NFData b) ⇒ NFData (These a b)

Since: these-0.7.1

Instance details

Defined in Data.These

Methods

rnfThese a b → () Source #

(NFData k, NFData v) ⇒ NFData (HashMap k v) 
Instance details

Defined in Data.HashMap.Internal

Methods

rnfHashMap k v → () Source #

(NFData k, NFData v) ⇒ NFData (Leaf k v) 
Instance details

Defined in Data.HashMap.Internal

Methods

rnfLeaf k v → () Source #

NFData (MVector s a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

rnfMVector s a → () Source #

(NFData a, NFData b) ⇒ NFData (a, b) 
Instance details

Defined in Control.DeepSeq

Methods

rnf ∷ (a, b) → () Source #

NFData (a → b)

This instance is for convenience and consistency with seq. This assumes that WHNF is equivalent to NF for functions.

Since: deepseq-1.3.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf ∷ (a → b) → () Source #

NFData a ⇒ NFData (Const a b)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfConst a b → () Source #

NFData (a :~: b)

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

rnf ∷ (a :~: b) → () Source #

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

Defined in PlutusCore.Core.Type

Methods

rnfType tyname uni ann → () Source #

(NFData fun, NFData ann, Closed uni, Everywhere uni NFData, NFData ParserError) ⇒ NFData (Error uni fun ann) Source # 
Instance details

Defined in PlutusCore.Error

Methods

rnfError uni fun ann → () Source #

(NFData machinecosts, Bounded fun, Enum fun) ⇒ NFData (MachineParameters machinecosts fun val) Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.MachineParameters

Methods

rnfMachineParameters machinecosts fun val → () Source #

NFData b ⇒ NFData (Tagged s b) 
Instance details

Defined in Data.Tagged

Methods

rnfTagged s b → () Source #

(NFData (f a), NFData (g a), NFData a) ⇒ NFData (These1 f g a)

Available always

Since: these-1.2

Instance details

Defined in Data.Functor.These

Methods

rnfThese1 f g a → () Source #

(NFData a1, NFData a2, NFData a3) ⇒ NFData (a1, a2, a3) 
Instance details

Defined in Control.DeepSeq

Methods

rnf ∷ (a1, a2, a3) → () Source #

(NFData1 f, NFData1 g, NFData a) ⇒ NFData (Product f g a)

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

rnfProduct f g a → () Source #

(NFData1 f, NFData1 g, NFData a) ⇒ NFData (Sum f g a)

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

rnfSum f g a → () Source #

NFData (a :~~: b)

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

rnf ∷ (a :~~: b) → () Source #

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

Defined in PlutusCore.Error

Methods

rnfTypeError term uni fun ann → () Source #

(NFData name, Everywhere uni NFData, NFData fun, NFData ann, Closed uni) ⇒ NFData (Program name uni fun ann) Source # 
Instance details

Defined in UntypedPlutusCore.Core.Type

Methods

rnfProgram name uni fun ann → () Source #

(NFData name, NFData fun, NFData ann, Everywhere uni NFData, Closed uni) ⇒ NFData (Term name uni fun ann) Source # 
Instance details

Defined in UntypedPlutusCore.Core.Type

Methods

rnfTerm name uni fun ann → () Source #

(NFData a1, NFData a2, NFData a3, NFData a4) ⇒ NFData (a1, a2, a3, a4) 
Instance details

Defined in Control.DeepSeq

Methods

rnf ∷ (a1, a2, a3, a4) → () Source #

(NFData1 f, NFData1 g, NFData a) ⇒ NFData (Compose f g a)

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

rnfCompose f g a → () Source #

(NFData tyname, NFData name, Everywhere uni NFData, NFData fun, NFData ann, Closed uni) ⇒ NFData (Program tyname name uni fun ann) Source # 
Instance details

Defined in PlutusCore.Core.Type

Methods

rnfProgram tyname name uni fun ann → () Source #

(NFData tyname, NFData name, NFData fun, NFData ann, Everywhere uni NFData, Closed uni) ⇒ NFData (Term tyname name uni fun ann) Source # 
Instance details

Defined in PlutusCore.Core.Type

Methods

rnfTerm tyname name uni fun ann → () Source #

(NFData tyname, NFData name, Closed uni, Everywhere uni NFData, NFData fun, NFData ann) ⇒ NFData (NormCheckError tyname name uni fun ann) Source # 
Instance details

Defined in PlutusCore.Error

Methods

rnfNormCheckError tyname name uni fun ann → () Source #

(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5) ⇒ NFData (a1, a2, a3, a4, a5) 
Instance details

Defined in Control.DeepSeq

Methods

rnf ∷ (a1, a2, a3, a4, a5) → () Source #

(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6) ⇒ NFData (a1, a2, a3, a4, a5, a6) 
Instance details

Defined in Control.DeepSeq

Methods

rnf ∷ (a1, a2, a3, a4, a5, a6) → () Source #

(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7) ⇒ NFData (a1, a2, a3, a4, a5, a6, a7) 
Instance details

Defined in Control.DeepSeq

Methods

rnf ∷ (a1, a2, a3, a4, a5, a6, a7) → () Source #

(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7, NFData a8) ⇒ NFData (a1, a2, a3, a4, a5, a6, a7, a8) 
Instance details

Defined in Control.DeepSeq

Methods

rnf ∷ (a1, a2, a3, a4, a5, a6, a7, a8) → () Source #

(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7, NFData a8, NFData a9) ⇒ NFData (a1, a2, a3, a4, a5, a6, a7, a8, a9) 
Instance details

Defined in Control.DeepSeq

Methods

rnf ∷ (a1, a2, a3, a4, a5, a6, a7, a8, a9) → () Source #

data Natural Source #

Natural number

Invariant: numbers <= 0xffffffffffffffff use the NS constructor

Instances

Instances details
FromJSON Natural 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON ∷ Value → Parser Natural

parseJSONList ∷ Value → Parser [Natural]

omittedFieldMaybe Natural

FromJSONKey Natural 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

fromJSONKey ∷ FromJSONKeyFunction Natural

fromJSONKeyList ∷ FromJSONKeyFunction [Natural]

ToJSON Natural 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSONNatural → Value

toEncodingNatural → Encoding

toJSONList ∷ [Natural] → Value

toEncodingList ∷ [Natural] → Encoding

omitFieldNaturalBool

ToJSONKey Natural 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSONKey ∷ ToJSONKeyFunction Natural

toJSONKeyList ∷ ToJSONKeyFunction [Natural]

Data Natural

Since: base-4.8.0.0

Instance details

Defined in Data.Data

Methods

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

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

toConstrNaturalConstr Source #

dataTypeOfNaturalDataType Source #

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

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

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

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

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

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

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

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

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

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

Bits Natural

Since: base-4.8.0

Instance details

Defined in GHC.Bits

Enum Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Enum

Ix Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Ix

Num Natural

Note that Natural's Num instance isn't a ring: no element but 0 has an additive inverse. It is a semiring though.

Since: base-4.8.0.0

Instance details

Defined in GHC.Num

Read Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Read

Integral Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Real

Real Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Real

Show Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Show

PrintfArg Natural

Since: base-4.8.0.0

Instance details

Defined in Text.Printf

Subtractive Natural 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Natural

Methods

(-)NaturalNatural → Difference Natural

FromField Natural 
Instance details

Defined in Data.Csv.Conversion

Methods

parseField ∷ Field → Parser Natural

ToField Natural 
Instance details

Defined in Data.Csv.Conversion

Methods

toFieldNatural → Field

NFData Natural

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnfNatural → () Source #

Eq Natural 
Instance details

Defined in GHC.Num.Natural

Methods

(==)NaturalNaturalBool Source #

(/=)NaturalNaturalBool Source #

Ord Natural 
Instance details

Defined in GHC.Num.Natural

Hashable Natural 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSaltIntNaturalInt Source #

hashNaturalInt Source #

NoThunks Natural 
Instance details

Defined in NoThunks.Class

ExMemoryUsage Natural Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemoryUsage

Pretty Natural 
Instance details

Defined in Prettyprinter.Internal

Methods

prettyNaturalDoc ann Source #

prettyList ∷ [Natural] → Doc ann Source #

UniformRange Natural 
Instance details

Defined in System.Random.Internal

Methods

uniformRMStatefulGen g m ⇒ (Natural, Natural) → g → m Natural Source #

Corecursive Natural 
Instance details

Defined in Data.Functor.Foldable

Methods

embedBase Natural NaturalNatural Source #

ana ∷ (a → Base Natural a) → a → Natural Source #

apo ∷ (a → Base Natural (Either Natural a)) → a → Natural Source #

postproRecursive Natural ⇒ (∀ b. Base Natural b → Base Natural b) → (a → Base Natural a) → a → Natural Source #

gpostpro ∷ (Recursive Natural, Monad m) ⇒ (∀ b. m (Base Natural b) → Base Natural (m b)) → (∀ c. Base Natural c → Base Natural c) → (a → Base Natural (m a)) → a → Natural Source #

Recursive Natural 
Instance details

Defined in Data.Functor.Foldable

Methods

projectNaturalBase Natural Natural Source #

cata ∷ (Base Natural a → a) → Natural → a Source #

para ∷ (Base Natural (Natural, a) → a) → Natural → a Source #

gpara ∷ (Corecursive Natural, Comonad w) ⇒ (∀ b. Base Natural (w b) → w (Base Natural b)) → (Base Natural (EnvT Natural w a) → a) → Natural → a Source #

preproCorecursive Natural ⇒ (∀ b. Base Natural b → Base Natural b) → (Base Natural a → a) → Natural → a Source #

gprepro ∷ (Corecursive Natural, Comonad w) ⇒ (∀ b. Base Natural (w b) → w (Base Natural b)) → (∀ c. Base Natural c → Base Natural c) → (Base Natural (w a) → a) → Natural → a Source #

Serialise Natural

Since: serialise-0.2.0.0

Instance details

Defined in Codec.Serialise.Class

Pretty Natural 
Instance details

Defined in Text.PrettyPrint.Annotated.WL

Methods

prettyNatural → Doc b

prettyList ∷ [Natural] → Doc b

KnownNat n ⇒ HasResolution (n ∷ Nat)

For example, Fixed 1000 will give you a Fixed with a resolution of 1000.

Instance details

Defined in Data.Fixed

Methods

resolution ∷ p n → Integer Source #

TestCoercion SNat

Since: base-4.18.0.0

Instance details

Defined in GHC.TypeNats

Methods

testCoercion ∷ ∀ (a ∷ k) (b ∷ k). SNat a → SNat b → Maybe (Coercion a b) Source #

TestEquality SNat

Since: base-4.18.0.0

Instance details

Defined in GHC.TypeNats

Methods

testEquality ∷ ∀ (a ∷ k) (b ∷ k). SNat a → SNat b → Maybe (a :~: b) Source #

DefaultPrettyBy config Natural 
Instance details

Defined in Text.PrettyBy.Internal

Methods

defaultPrettyBy ∷ config → NaturalDoc ann Source #

defaultPrettyListBy ∷ config → [Natural] → Doc ann Source #

PrettyDefaultBy config NaturalPrettyBy config Natural
>>> prettyBy () (123 :: Natural)
123
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyBy ∷ config → NaturalDoc ann Source #

prettyListBy ∷ config → [Natural] → Doc ann Source #

GCompare SNat 
Instance details

Defined in Data.GADT.Internal

Methods

gcompare ∷ ∀ (a ∷ k) (b ∷ k). SNat a → SNat b → GOrdering a b Source #

GEq SNat 
Instance details

Defined in Data.GADT.Internal

Methods

geq ∷ ∀ (a ∷ k) (b ∷ k). SNat a → SNat b → Maybe (a :~: b) Source #

GShow SNat 
Instance details

Defined in Data.GADT.Internal

Methods

gshowsPrec ∷ ∀ (a ∷ k). IntSNat a → ShowS Source #

Lift Natural 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

liftQuote m ⇒ Natural → m Exp Source #

liftTyped ∷ ∀ (m ∷ TypeType). Quote m ⇒ NaturalCode m Natural Source #

KnownBuiltinTypeIn DefaultUni term IntegerMakeKnownIn DefaultUni term Natural Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

makeKnownNaturalBuiltinResult term Source #

KnownBuiltinTypeIn DefaultUni term IntegerReadKnownIn DefaultUni term Natural Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

readKnown ∷ term → ReadKnownM Natural Source #

KnownNat n ⇒ Reifies (n ∷ Nat) Integer 
Instance details

Defined in Data.Reflection

Methods

reflect ∷ proxy n → Integer

KnownTypeAst tyname DefaultUni Natural Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

typeAstType tyname DefaultUni () Source #

GTraversable (n ∷ Nat) (f ∷ k1 → Type) (g ∷ k1 → Type) (Rec (P n f a') (f a) ∷ k2 → Type) (Rec (P n g a') (g a) ∷ k2 → Type) 
Instance details

Defined in Barbies.Generics.Traversable

Methods

gtraverse ∷ ∀ t (x ∷ k20). Applicative t ⇒ Proxy n → (∀ (a0 ∷ k10). f a0 → t (g a0)) → Rec (P n f a') (f a) x → t (Rec (P n g a') (g a) x)

Traversable h ⇒ GTraversable (n ∷ Nat) (f ∷ k1 → Type) (g ∷ k1 → Type) (Rec (h (P n f a)) (h (f a)) ∷ k2 → Type) (Rec (h (P n g a)) (h (g a)) ∷ k2 → Type) 
Instance details

Defined in Barbies.Generics.Traversable

Methods

gtraverse ∷ ∀ t (x ∷ k20). Applicative t ⇒ Proxy n → (∀ (a0 ∷ k10). f a0 → t (g a0)) → Rec (h (P n f a)) (h (f a)) x → t (Rec (h (P n g a)) (h (g a)) x)

type Difference Natural 
Instance details

Defined in Basement.Numerical.Subtractive

type Difference Natural = Maybe Natural
type Base Natural 
Instance details

Defined in Data.Functor.Foldable

type Compare (a ∷ Natural) (b ∷ Natural) 
Instance details

Defined in Data.Type.Ord

type Compare (a ∷ Natural) (b ∷ Natural) = CmpNat a b
type IsBuiltin DefaultUni Natural Source # 
Instance details

Defined in PlutusCore.Default.Universe

type ToHoles DefaultUni Natural Source # 
Instance details

Defined in PlutusCore.Default.Universe

type ToBinds DefaultUni acc Natural Source # 
Instance details

Defined in PlutusCore.Default.Universe

data NonEmpty a Source #

Non-empty (and non-strict) list type.

Since: base-4.9.0.0

Constructors

a :| [a] infixr 5 

Instances

Instances details
FromJSON1 NonEmpty 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

liftParseJSONMaybe a → (Value → Parser a) → (Value → Parser [a]) → Value → Parser (NonEmpty a)

liftParseJSONListMaybe a → (Value → Parser a) → (Value → Parser [a]) → Value → Parser [NonEmpty a]

liftOmittedFieldMaybe a → Maybe (NonEmpty a)

ToJSON1 NonEmpty 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

liftToJSON ∷ (a → Bool) → (a → Value) → ([a] → Value) → NonEmpty a → Value

liftToJSONList ∷ (a → Bool) → (a → Value) → ([a] → Value) → [NonEmpty a] → Value

liftToEncoding ∷ (a → Bool) → (a → Encoding) → ([a] → Encoding) → NonEmpty a → Encoding

liftToEncodingList ∷ (a → Bool) → (a → Encoding) → ([a] → Encoding) → [NonEmpty a] → Encoding

liftOmitField ∷ (a → Bool) → NonEmpty a → Bool

MonadFix NonEmpty

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.Fix

Methods

mfix ∷ (a → NonEmpty a) → NonEmpty a Source #

Foldable NonEmpty

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

Methods

foldMonoid m ⇒ NonEmpty m → m Source #

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

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

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

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

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

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

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

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

toListNonEmpty a → [a] Source #

nullNonEmpty a → Bool Source #

lengthNonEmpty a → Int Source #

elemEq a ⇒ a → NonEmpty a → Bool Source #

maximumOrd a ⇒ NonEmpty a → a Source #

minimumOrd a ⇒ NonEmpty a → a Source #

sumNum a ⇒ NonEmpty a → a Source #

productNum a ⇒ NonEmpty a → a Source #

Eq1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq ∷ (a → b → Bool) → NonEmpty a → NonEmpty b → Bool Source #

Ord1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare ∷ (a → b → Ordering) → NonEmpty a → NonEmpty b → Ordering Source #

Read1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec ∷ (IntReadS a) → ReadS [a] → IntReadS (NonEmpty a) Source #

liftReadList ∷ (IntReadS a) → ReadS [a] → ReadS [NonEmpty a] Source #

liftReadPrecReadPrec a → ReadPrec [a] → ReadPrec (NonEmpty a) Source #

liftReadListPrecReadPrec a → ReadPrec [a] → ReadPrec [NonEmpty a] Source #

Show1 NonEmpty

Since: base-4.10.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec ∷ (Int → a → ShowS) → ([a] → ShowS) → IntNonEmpty a → ShowS Source #

liftShowList ∷ (Int → a → ShowS) → ([a] → ShowS) → [NonEmpty a] → ShowS Source #

Traversable NonEmpty

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

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

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

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

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

Applicative NonEmpty

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

pure ∷ a → NonEmpty a Source #

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

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

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

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

Functor NonEmpty

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

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

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

Monad NonEmpty

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(>>=)NonEmpty a → (a → NonEmpty b) → NonEmpty b Source #

(>>)NonEmpty a → NonEmpty b → NonEmpty b Source #

return ∷ a → NonEmpty a Source #

NFData1 NonEmpty

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf ∷ (a → ()) → NonEmpty a → () Source #

Hashable1 NonEmpty

Since: hashable-1.3.1.0

Instance details

Defined in Data.Hashable.Class

Methods

liftHashWithSalt ∷ (Int → a → Int) → IntNonEmpty a → Int Source #

Traversable1 NonEmpty 
Instance details

Defined in Data.Semigroup.Traversable.Class

Methods

traverse1Apply f ⇒ (a → f b) → NonEmpty a → f (NonEmpty b) Source #

sequence1Apply f ⇒ NonEmpty (f b) → f (NonEmpty b) Source #

Generic1 NonEmpty 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 NonEmpty ∷ k → Type Source #

Methods

from1 ∷ ∀ (a ∷ k). NonEmpty a → Rep1 NonEmpty a Source #

to1 ∷ ∀ (a ∷ k). Rep1 NonEmpty a → NonEmpty a Source #

Foldable1WithIndex Int NonEmpty 
Instance details

Defined in WithIndex

Methods

ifoldMap1Semigroup m ⇒ (Int → a → m) → NonEmpty a → m

ifoldMap1'Semigroup m ⇒ (Int → a → m) → NonEmpty a → m

ifoldrMap1 ∷ (Int → a → b) → (Int → a → b → b) → NonEmpty a → b

ifoldlMap1' ∷ (Int → a → b) → (Int → b → a → b) → NonEmpty a → b

ifoldlMap1 ∷ (Int → a → b) → (Int → b → a → b) → NonEmpty a → b

ifoldrMap1' ∷ (Int → a → b) → (Int → a → b → b) → NonEmpty a → b

FoldableWithIndex Int NonEmpty 
Instance details

Defined in WithIndex

Methods

ifoldMapMonoid m ⇒ (Int → a → m) → NonEmpty a → m

ifoldMap'Monoid m ⇒ (Int → a → m) → NonEmpty a → m

ifoldr ∷ (Int → a → b → b) → b → NonEmpty a → b

ifoldl ∷ (Int → b → a → b) → b → NonEmpty a → b

ifoldr' ∷ (Int → a → b → b) → b → NonEmpty a → b

ifoldl' ∷ (Int → b → a → b) → b → NonEmpty a → b

FunctorWithIndex Int NonEmpty 
Instance details

Defined in WithIndex

Methods

imap ∷ (Int → a → b) → NonEmpty a → NonEmpty b

TraversableWithIndex Int NonEmpty 
Instance details

Defined in WithIndex

Methods

itraverseApplicative f ⇒ (Int → a → f b) → NonEmpty a → f (NonEmpty b)

PrettyBy config a ⇒ DefaultPrettyBy config (NonEmpty a) 
Instance details

Defined in Text.PrettyBy.Internal

Methods

defaultPrettyBy ∷ config → NonEmpty a → Doc ann Source #

defaultPrettyListBy ∷ config → [NonEmpty a] → Doc ann Source #

PrettyDefaultBy config (NonEmpty a) ⇒ PrettyBy config (NonEmpty a)

prettyBy for NonEmpty a is defined in terms of prettyListBy by default.

>>> prettyBy () (True :| [False])
[True, False]
>>> prettyBy () ('a' :| "bc")
abc
>>> prettyBy () (Just False :| [Nothing, Just True])
[False, True]
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyBy ∷ config → NonEmpty a → Doc ann Source #

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

Lift a ⇒ Lift (NonEmpty a ∷ Type)

Since: template-haskell-2.15.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

liftQuote m ⇒ NonEmpty a → m Exp Source #

liftTyped ∷ ∀ (m ∷ TypeType). Quote m ⇒ NonEmpty a → Code m (NonEmpty a) Source #

FromJSON a ⇒ FromJSON (NonEmpty a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON ∷ Value → Parser (NonEmpty a)

parseJSONList ∷ Value → Parser [NonEmpty a]

omittedFieldMaybe (NonEmpty a)

ToJSON a ⇒ ToJSON (NonEmpty a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSONNonEmpty a → Value

toEncodingNonEmpty a → Encoding

toJSONList ∷ [NonEmpty a] → Value

toEncodingList ∷ [NonEmpty a] → Encoding

omitFieldNonEmpty a → Bool

Data a ⇒ Data (NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in Data.Data

Methods

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

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

toConstrNonEmpty a → Constr Source #

dataTypeOfNonEmpty a → DataType Source #

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

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

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

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

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

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

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

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

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

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

Semigroup (NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(<>)NonEmpty a → NonEmpty a → NonEmpty a Source #

sconcatNonEmpty (NonEmpty a) → NonEmpty a Source #

stimesIntegral b ⇒ b → NonEmpty a → NonEmpty a Source #

Generic (NonEmpty a) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (NonEmpty a) ∷ TypeType Source #

Methods

fromNonEmpty a → Rep (NonEmpty a) x Source #

toRep (NonEmpty a) x → NonEmpty a Source #

IsList (NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in GHC.IsList

Associated Types

type Item (NonEmpty a) Source #

Methods

fromList ∷ [Item (NonEmpty a)] → NonEmpty a Source #

fromListNInt → [Item (NonEmpty a)] → NonEmpty a Source #

toListNonEmpty a → [Item (NonEmpty a)] Source #

Read a ⇒ Read (NonEmpty a)

Since: base-4.11.0.0

Instance details

Defined in GHC.Read

Show a ⇒ Show (NonEmpty a)

Since: base-4.11.0.0

Instance details

Defined in GHC.Show

NFData a ⇒ NFData (NonEmpty a)

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnfNonEmpty a → () Source #

Eq a ⇒ Eq (NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

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

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

Ord a ⇒ Ord (NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

compareNonEmpty a → NonEmpty a → Ordering Source #

(<)NonEmpty a → NonEmpty a → Bool Source #

(<=)NonEmpty a → NonEmpty a → Bool Source #

(>)NonEmpty a → NonEmpty a → Bool Source #

(>=)NonEmpty a → NonEmpty a → Bool Source #

maxNonEmpty a → NonEmpty a → NonEmpty a Source #

minNonEmpty a → NonEmpty a → NonEmpty a Source #

Hashable a ⇒ Hashable (NonEmpty a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSaltIntNonEmpty a → Int Source #

hashNonEmpty a → Int Source #

Ixed (NonEmpty a) 
Instance details

Defined in Control.Lens.At

Methods

ix ∷ Index (NonEmpty a) → Traversal' (NonEmpty a) (IxValue (NonEmpty a))

Reversing (NonEmpty a) 
Instance details

Defined in Control.Lens.Internal.Iso

Methods

reversingNonEmpty a → NonEmpty a

Wrapped (NonEmpty a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (NonEmpty a)

Methods

_Wrapped' ∷ Iso' (NonEmpty a) (Unwrapped (NonEmpty a))

Ixed (NonEmpty a) 
Instance details

Defined in Lens.Micro.Internal

Methods

ixIndex (NonEmpty a) → Traversal' (NonEmpty a) (IxValue (NonEmpty a)) Source #

GrowingAppend (NonEmpty a) 
Instance details

Defined in Data.MonoTraversable

MonoFoldable (NonEmpty a) 
Instance details

Defined in Data.MonoTraversable

Methods

ofoldMapMonoid m ⇒ (Element (NonEmpty a) → m) → NonEmpty a → m Source #

ofoldr ∷ (Element (NonEmpty a) → b → b) → b → NonEmpty a → b Source #

ofoldl' ∷ (a0 → Element (NonEmpty a) → a0) → a0 → NonEmpty a → a0 Source #

otoListNonEmpty a → [Element (NonEmpty a)] Source #

oall ∷ (Element (NonEmpty a) → Bool) → NonEmpty a → Bool Source #

oany ∷ (Element (NonEmpty a) → Bool) → NonEmpty a → Bool Source #

onullNonEmpty a → Bool Source #

olengthNonEmpty a → Int Source #

olength64NonEmpty a → Int64 Source #

ocompareLengthIntegral i ⇒ NonEmpty a → i → Ordering Source #

otraverse_Applicative f ⇒ (Element (NonEmpty a) → f b) → NonEmpty a → f () Source #

ofor_Applicative f ⇒ NonEmpty a → (Element (NonEmpty a) → f b) → f () Source #

omapM_Applicative m ⇒ (Element (NonEmpty a) → m ()) → NonEmpty a → m () Source #

oforM_Applicative m ⇒ NonEmpty a → (Element (NonEmpty a) → m ()) → m () Source #

ofoldlMMonad m ⇒ (a0 → Element (NonEmpty a) → m a0) → a0 → NonEmpty a → m a0 Source #

ofoldMap1ExSemigroup m ⇒ (Element (NonEmpty a) → m) → NonEmpty a → m Source #

ofoldr1Ex ∷ (Element (NonEmpty a) → Element (NonEmpty a) → Element (NonEmpty a)) → NonEmpty a → Element (NonEmpty a) Source #

ofoldl1Ex' ∷ (Element (NonEmpty a) → Element (NonEmpty a) → Element (NonEmpty a)) → NonEmpty a → Element (NonEmpty a) Source #

headExNonEmpty a → Element (NonEmpty a) Source #

lastExNonEmpty a → Element (NonEmpty a) Source #

unsafeHeadNonEmpty a → Element (NonEmpty a) Source #

unsafeLastNonEmpty a → Element (NonEmpty a) Source #

maximumByEx ∷ (Element (NonEmpty a) → Element (NonEmpty a) → Ordering) → NonEmpty a → Element (NonEmpty a) Source #

minimumByEx ∷ (Element (NonEmpty a) → Element (NonEmpty a) → Ordering) → NonEmpty a → Element (NonEmpty a) Source #

oelemElement (NonEmpty a) → NonEmpty a → Bool Source #

onotElemElement (NonEmpty a) → NonEmpty a → Bool Source #

MonoFunctor (NonEmpty a) 
Instance details

Defined in Data.MonoTraversable

Methods

omap ∷ (Element (NonEmpty a) → Element (NonEmpty a)) → NonEmpty a → NonEmpty a Source #

MonoPointed (NonEmpty a) 
Instance details

Defined in Data.MonoTraversable

Methods

opointElement (NonEmpty a) → NonEmpty a Source #

MonoTraversable (NonEmpty a) 
Instance details

Defined in Data.MonoTraversable

Methods

otraverseApplicative f ⇒ (Element (NonEmpty a) → f (Element (NonEmpty a))) → NonEmpty a → f (NonEmpty a) Source #

omapMApplicative m ⇒ (Element (NonEmpty a) → m (Element (NonEmpty a))) → NonEmpty a → m (NonEmpty a) Source #

SemiSequence (NonEmpty a) 
Instance details

Defined in Data.Sequences

Associated Types

type Index (NonEmpty a) Source #

NoThunks a ⇒ NoThunks (NonEmpty a) 
Instance details

Defined in NoThunks.Class

Pretty a ⇒ Pretty (NonEmpty a) 
Instance details

Defined in Prettyprinter.Internal

Methods

prettyNonEmpty a → Doc ann Source #

prettyList ∷ [NonEmpty a] → Doc ann Source #

Corecursive (NonEmpty a) 
Instance details

Defined in Data.Functor.Foldable

Methods

embedBase (NonEmpty a) (NonEmpty a) → NonEmpty a Source #

ana ∷ (a0 → Base (NonEmpty a) a0) → a0 → NonEmpty a Source #

apo ∷ (a0 → Base (NonEmpty a) (Either (NonEmpty a) a0)) → a0 → NonEmpty a Source #

postproRecursive (NonEmpty a) ⇒ (∀ b. Base (NonEmpty a) b → Base (NonEmpty a) b) → (a0 → Base (NonEmpty a) a0) → a0 → NonEmpty a Source #

gpostpro ∷ (Recursive (NonEmpty a), Monad m) ⇒ (∀ b. m (Base (NonEmpty a) b) → Base (NonEmpty a) (m b)) → (∀ c. Base (NonEmpty a) c → Base (NonEmpty a) c) → (a0 → Base (NonEmpty a) (m a0)) → a0 → NonEmpty a Source #

Recursive (NonEmpty a) 
Instance details

Defined in Data.Functor.Foldable

Methods

projectNonEmpty a → Base (NonEmpty a) (NonEmpty a) Source #

cata ∷ (Base (NonEmpty a) a0 → a0) → NonEmpty a → a0 Source #

para ∷ (Base (NonEmpty a) (NonEmpty a, a0) → a0) → NonEmpty a → a0 Source #

gpara ∷ (Corecursive (NonEmpty a), Comonad w) ⇒ (∀ b. Base (NonEmpty a) (w b) → w (Base (NonEmpty a) b)) → (Base (NonEmpty a) (EnvT (NonEmpty a) w a0) → a0) → NonEmpty a → a0 Source #

preproCorecursive (NonEmpty a) ⇒ (∀ b. Base (NonEmpty a) b → Base (NonEmpty a) b) → (Base (NonEmpty a) a0 → a0) → NonEmpty a → a0 Source #

gprepro ∷ (Corecursive (NonEmpty a), Comonad w) ⇒ (∀ b. Base (NonEmpty a) (w b) → w (Base (NonEmpty a) b)) → (∀ c. Base (NonEmpty a) c → Base (NonEmpty a) c) → (Base (NonEmpty a) (w a0) → a0) → NonEmpty a → a0 Source #

Serialise a ⇒ Serialise (NonEmpty a)

Since: serialise-0.2.0.0

Instance details

Defined in Codec.Serialise.Class

Pretty a ⇒ Pretty (NonEmpty a) 
Instance details

Defined in Text.PrettyPrint.Annotated.WL

Methods

prettyNonEmpty a → Doc b

prettyList ∷ [NonEmpty a] → Doc b

t ~ NonEmpty b ⇒ Rewrapped (NonEmpty a) t 
Instance details

Defined in Control.Lens.Wrapped

Reference n t ⇒ Reference (NonEmpty n) t Source # 
Instance details

Defined in PlutusCore.Check.Scoping

Methods

referenceVia ∷ (∀ name. ToScopedName name ⇒ name → NameAnn) → NonEmpty n → t NameAnn → t NameAnn Source #

Each (NonEmpty a) (NonEmpty b) a b 
Instance details

Defined in Control.Lens.Each

Methods

each ∷ Traversal (NonEmpty a) (NonEmpty b) a b

Each (NonEmpty a) (NonEmpty b) a b 
Instance details

Defined in Lens.Micro.Internal

Methods

eachTraversal (NonEmpty a) (NonEmpty b) a b Source #

type Rep1 NonEmpty

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep (NonEmpty a)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Item (NonEmpty a) 
Instance details

Defined in GHC.IsList

type Item (NonEmpty a) = a
type Index (NonEmpty a) 
Instance details

Defined in Control.Lens.At

type Index (NonEmpty a) = Int
type IxValue (NonEmpty a) 
Instance details

Defined in Control.Lens.At

type IxValue (NonEmpty a) = a
type Unwrapped (NonEmpty a) 
Instance details

Defined in Control.Lens.Wrapped

type Unwrapped (NonEmpty a) = (a, [a])
type Index (NonEmpty a) 
Instance details

Defined in Lens.Micro.Internal

type Index (NonEmpty a) = Int
type IxValue (NonEmpty a) 
Instance details

Defined in Lens.Micro.Internal

type IxValue (NonEmpty a) = a
type Element (NonEmpty a) 
Instance details

Defined in Data.MonoTraversable

type Element (NonEmpty a) = a
type Index (NonEmpty a) 
Instance details

Defined in Data.Sequences

type Index (NonEmpty a) = Int
type Base (NonEmpty a) 
Instance details

Defined in Data.Functor.Foldable

type Base (NonEmpty a) = NonEmptyF a

data Word8 Source #

8-bit unsigned integer type

Instances

Instances details
FromJSON Word8 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON ∷ Value → Parser Word8

parseJSONList ∷ Value → Parser [Word8]

omittedFieldMaybe Word8

FromJSONKey Word8 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

fromJSONKey ∷ FromJSONKeyFunction Word8

fromJSONKeyList ∷ FromJSONKeyFunction [Word8]

ToJSON Word8 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSONWord8 → Value

toEncodingWord8 → Encoding

toJSONList ∷ [Word8] → Value

toEncodingList ∷ [Word8] → Encoding

omitFieldWord8Bool

ToJSONKey Word8 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSONKey ∷ ToJSONKeyFunction Word8

toJSONKeyList ∷ ToJSONKeyFunction [Word8]

Data Word8

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

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

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

toConstrWord8Constr Source #

dataTypeOfWord8DataType Source #

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

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

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

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

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

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

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

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

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

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

Storable Word8

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOfWord8Int Source #

alignmentWord8Int Source #

peekElemOffPtr Word8IntIO Word8 Source #

pokeElemOffPtr Word8IntWord8IO () Source #

peekByteOffPtr b → IntIO Word8 Source #

pokeByteOffPtr b → IntWord8IO () Source #

peekPtr Word8IO Word8 Source #

pokePtr Word8Word8IO () Source #

Bits Word8

Since: base-2.1

Instance details

Defined in GHC.Word

FiniteBits Word8

Since: base-4.6.0.0

Instance details

Defined in GHC.Word

Bounded Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Enum Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Ix Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Num Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Read Word8

Since: base-2.1

Instance details

Defined in GHC.Read

Integral Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Real Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Show Word8

Since: base-2.1

Instance details

Defined in GHC.Word

PrintfArg Word8

Since: base-2.1

Instance details

Defined in Text.Printf

BitOps Word8 
Instance details

Defined in Basement.Bits

Methods

(.&.)Word8Word8Word8

(.|.)Word8Word8Word8

(.^.)Word8Word8Word8

(.<<.)Word8 → CountOf BoolWord8

(.>>.)Word8 → CountOf BoolWord8

bit ∷ Offset BoolWord8

isBitSetWord8 → Offset BoolBool

setBitWord8 → Offset BoolWord8

clearBitWord8 → Offset BoolWord8

FiniteBitsOps Word8 
Instance details

Defined in Basement.Bits

Methods

numberOfBitsWord8 → CountOf Bool

rotateLWord8 → CountOf BoolWord8

rotateRWord8 → CountOf BoolWord8

popCountWord8 → CountOf Bool

bitFlipWord8Word8

countLeadingZerosWord8 → CountOf Bool

countTrailingZerosWord8 → CountOf Bool

Subtractive Word8 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Word8

Methods

(-)Word8Word8 → Difference Word8

PrimMemoryComparable Word8 
Instance details

Defined in Basement.PrimType

PrimType Word8 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Word8Nat

Methods

primSizeInBytesProxy Word8 → CountOf Word8

primShiftToBytesProxy Word8Int

primBaUIndexByteArray# → Offset Word8Word8

primMbaURead ∷ PrimMonad prim ⇒ MutableByteArray# (PrimState prim) → Offset Word8 → prim Word8

primMbaUWrite ∷ PrimMonad prim ⇒ MutableByteArray# (PrimState prim) → Offset Word8Word8 → prim ()

primAddrIndexAddr# → Offset Word8Word8

primAddrRead ∷ PrimMonad prim ⇒ Addr# → Offset Word8 → prim Word8

primAddrWrite ∷ PrimMonad prim ⇒ Addr# → Offset Word8Word8 → prim ()

FromField Word8 
Instance details

Defined in Data.Csv.Conversion

Methods

parseField ∷ Field → Parser Word8

ToField Word8 
Instance details

Defined in Data.Csv.Conversion

Methods

toFieldWord8 → Field

Default Word8 
Instance details

Defined in Data.Default.Class

Methods

defWord8 Source #

NFData Word8 
Instance details

Defined in Control.DeepSeq

Methods

rnfWord8 → () Source #

Eq Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

(==)Word8Word8Bool Source #

(/=)Word8Word8Bool Source #

Ord Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

compareWord8Word8Ordering Source #

(<)Word8Word8Bool Source #

(<=)Word8Word8Bool Source #

(>)Word8Word8Bool Source #

(>=)Word8Word8Bool Source #

maxWord8Word8Word8 Source #

minWord8Word8Word8 Source #

Hashable Word8 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSaltIntWord8Int Source #

hashWord8Int Source #

NoThunks Word8 
Instance details

Defined in NoThunks.Class

ExMemoryUsage Word8 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemoryUsage

Pretty Word8 
Instance details

Defined in Prettyprinter.Internal

Methods

prettyWord8Doc ann Source #

prettyList ∷ [Word8] → Doc ann Source #

Prim Word8 
Instance details

Defined in Data.Primitive.Types

Uniform Word8 
Instance details

Defined in System.Random.Internal

Methods

uniformMStatefulGen g m ⇒ g → m Word8 Source #

UniformRange Word8 
Instance details

Defined in System.Random.Internal

Methods

uniformRMStatefulGen g m ⇒ (Word8, Word8) → g → m Word8 Source #

Serialise Word8

Since: serialise-0.2.0.0

Instance details

Defined in Codec.Serialise.Class

ByteSource Word8 
Instance details

Defined in Data.UUID.Types.Internal.Builder

Methods

(/-/) ∷ ByteSink Word8 g → Word8 → g

Unbox Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

Pretty Word8 
Instance details

Defined in Text.PrettyPrint.Annotated.WL

Methods

prettyWord8 → Doc b

prettyList ∷ [Word8] → Doc b

DefaultPrettyBy config Word8 
Instance details

Defined in Text.PrettyBy.Internal

Methods

defaultPrettyBy ∷ config → Word8Doc ann Source #

defaultPrettyListBy ∷ config → [Word8] → Doc ann Source #

PrettyDefaultBy config Word8PrettyBy config Word8 
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyBy ∷ config → Word8Doc ann Source #

prettyListBy ∷ config → [Word8] → Doc ann Source #

Lift Word8 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

liftQuote m ⇒ Word8 → m Exp Source #

liftTyped ∷ ∀ (m ∷ TypeType). Quote m ⇒ Word8Code m Word8 Source #

Vector Vector Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

KnownBuiltinTypeIn DefaultUni term IntegerMakeKnownIn DefaultUni term Word8 Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

makeKnownWord8BuiltinResult term Source #

KnownBuiltinTypeIn DefaultUni term IntegerReadKnownIn DefaultUni term Word8 Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

readKnown ∷ term → ReadKnownM Word8 Source #

Cons ByteString ByteString Word8 Word8 
Instance details

Defined in Control.Lens.Cons

Cons ByteString ByteString Word8 Word8 
Instance details

Defined in Control.Lens.Cons

Snoc ByteString ByteString Word8 Word8 
Instance details

Defined in Control.Lens.Cons

Snoc ByteString ByteString Word8 Word8 
Instance details

Defined in Control.Lens.Cons

KnownTypeAst tyname DefaultUni Word8 Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

typeAstType tyname DefaultUni () Source #

AsByteString [Word8] 
Instance details

Defined in Data.ByteString.Convert

type NatNumMaxBound Word8 
Instance details

Defined in Basement.Nat

type NatNumMaxBound Word8 = 255
type Difference Word8 
Instance details

Defined in Basement.Numerical.Subtractive

type Difference Word8 = Word8
type PrimSize Word8 
Instance details

Defined in Basement.PrimType

type PrimSize Word8 = 1
newtype Vector Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

type ByteSink Word8 g 
Instance details

Defined in Data.UUID.Types.Internal.Builder

type ByteSink Word8 g = Takes1Byte g
newtype MVector s Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

type IsBuiltin DefaultUni Word8 Source # 
Instance details

Defined in PlutusCore.Default.Universe

type ToHoles DefaultUni Word8 Source # 
Instance details

Defined in PlutusCore.Default.Universe

type ToBinds DefaultUni acc Word8 Source # 
Instance details

Defined in PlutusCore.Default.Universe

class Applicative f ⇒ Alternative (f ∷ TypeType) where Source #

A monoid on applicative functors.

If defined, some and many should be the least solutions of the equations:

Minimal complete definition

empty, (<|>)

Methods

empty ∷ f a Source #

The identity of <|>

(<|>) ∷ f a → f a → f a infixl 3 Source #

An associative binary operation

some ∷ f a → f [a] Source #

One or more.

many ∷ f a → f [a] Source #

Zero or more.

Instances

Instances details
Alternative IResult 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

empty ∷ IResult a Source #

(<|>) ∷ IResult a → IResult a → IResult a Source #

some ∷ IResult a → IResult [a] Source #

many ∷ IResult a → IResult [a] Source #

Alternative Parser 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

empty ∷ Parser a Source #

(<|>) ∷ Parser a → Parser a → Parser a Source #

some ∷ Parser a → Parser [a] Source #

many ∷ Parser a → Parser [a] Source #

Alternative Result 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

empty ∷ Result a Source #

(<|>) ∷ Result a → Result a → Result a Source #

some ∷ Result a → Result [a] Source #

many ∷ Result a → Result [a] Source #

Alternative ZipList

Since: base-4.11.0.0

Instance details

Defined in Control.Applicative

Methods

emptyZipList a Source #

(<|>)ZipList a → ZipList a → ZipList a Source #

someZipList a → ZipList [a] Source #

manyZipList a → ZipList [a] Source #

Alternative STM

Takes the first non-retrying STM action.

Since: base-4.8.0.0

Instance details

Defined in GHC.Conc.Sync

Methods

emptySTM a Source #

(<|>)STM a → STM a → STM a Source #

someSTM a → STM [a] Source #

manySTM a → STM [a] Source #

Alternative P

Since: base-4.5.0.0

Instance details

Defined in Text.ParserCombinators.ReadP

Methods

empty ∷ P a Source #

(<|>) ∷ P a → P a → P a Source #

some ∷ P a → P [a] Source #

many ∷ P a → P [a] Source #

Alternative ReadP

Since: base-4.6.0.0

Instance details

Defined in Text.ParserCombinators.ReadP

Methods

emptyReadP a Source #

(<|>)ReadP a → ReadP a → ReadP a Source #

someReadP a → ReadP [a] Source #

manyReadP a → ReadP [a] Source #

Alternative ReadPrec

Since: base-4.6.0.0

Instance details

Defined in Text.ParserCombinators.ReadPrec

Methods

emptyReadPrec a Source #

(<|>)ReadPrec a → ReadPrec a → ReadPrec a Source #

someReadPrec a → ReadPrec [a] Source #

manyReadPrec a → ReadPrec [a] Source #

Alternative Parser 
Instance details

Defined in Data.Csv.Conversion

Methods

empty ∷ Parser a Source #

(<|>) ∷ Parser a → Parser a → Parser a Source #

some ∷ Parser a → Parser [a] Source #

many ∷ Parser a → Parser [a] Source #

Alternative Seq

Since: containers-0.5.4

Instance details

Defined in Data.Sequence.Internal

Methods

emptySeq a Source #

(<|>)Seq a → Seq a → Seq a Source #

someSeq a → Seq [a] Source #

manySeq a → Seq [a] Source #

Alternative DList 
Instance details

Defined in Data.DList.Internal

Methods

emptyDList a Source #

(<|>)DList a → DList a → DList a Source #

someDList a → DList [a] Source #

manyDList a → DList [a] Source #

Alternative IO

Takes the first non-throwing IO action's result. empty throws an exception.

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

emptyIO a Source #

(<|>)IO a → IO a → IO a Source #

someIO a → IO [a] Source #

manyIO a → IO [a] Source #

Alternative EvaluationResult Source # 
Instance details

Defined in PlutusCore.Evaluation.Result

Alternative DecodeUniM Source # 
Instance details

Defined in Universe.Core

Alternative Array 
Instance details

Defined in Data.Primitive.Array

Methods

emptyArray a Source #

(<|>)Array a → Array a → Array a Source #

someArray a → Array [a] Source #

manyArray a → Array [a] Source #

Alternative SmallArray 
Instance details

Defined in Data.Primitive.SmallArray

Alternative Vector 
Instance details

Defined in Data.Vector

Methods

emptyVector a Source #

(<|>)Vector a → Vector a → Vector a Source #

someVector a → Vector [a] Source #

manyVector a → Vector [a] Source #

Alternative Maybe

Picks the leftmost Just value, or, alternatively, Nothing.

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

emptyMaybe a Source #

(<|>)Maybe a → Maybe a → Maybe a Source #

someMaybe a → Maybe [a] Source #

manyMaybe a → Maybe [a] Source #

Alternative List

Combines lists by concatenation, starting from the empty list.

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

empty ∷ [a] Source #

(<|>) ∷ [a] → [a] → [a] Source #

some ∷ [a] → [[a]] Source #

many ∷ [a] → [[a]] Source #

Alternative (Parser i) 
Instance details

Defined in Data.Attoparsec.Internal.Types

Methods

empty ∷ Parser i a Source #

(<|>) ∷ Parser i a → Parser i a → Parser i a Source #

some ∷ Parser i a → Parser i [a] Source #

many ∷ Parser i a → Parser i [a] Source #

MonadPlus m ⇒ Alternative (WrappedMonad m)

Since: base-2.1

Instance details

Defined in Control.Applicative

ArrowPlus a ⇒ Alternative (ArrowMonad a)

Since: base-4.6.0.0

Instance details

Defined in Control.Arrow

Methods

emptyArrowMonad a a0 Source #

(<|>)ArrowMonad a a0 → ArrowMonad a a0 → ArrowMonad a a0 Source #

someArrowMonad a a0 → ArrowMonad a [a0] Source #

manyArrowMonad a a0 → ArrowMonad a [a0] Source #

Alternative (ProxyTypeType)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

emptyProxy a Source #

(<|>)Proxy a → Proxy a → Proxy a Source #

someProxy a → Proxy [a] Source #

manyProxy a → Proxy [a] Source #

Alternative (U1TypeType)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

emptyU1 a Source #

(<|>)U1 a → U1 a → U1 a Source #

someU1 a → U1 [a] Source #

manyU1 a → U1 [a] Source #

Alternative v ⇒ Alternative (Free v)

This violates the Alternative laws, handle with care.

Instance details

Defined in Control.Monad.Free

Methods

emptyFree v a Source #

(<|>)Free v a → Free v a → Free v a Source #

someFree v a → Free v [a] Source #

manyFree v a → Free v [a] Source #

Monad m ⇒ Alternative (GenT m) 
Instance details

Defined in Hedgehog.Internal.Gen

Methods

emptyGenT m a Source #

(<|>)GenT m a → GenT m a → GenT m a Source #

someGenT m a → GenT m [a] Source #

manyGenT m a → GenT m [a] Source #

MonadPlus m ⇒ Alternative (PropertyT m) 
Instance details

Defined in Hedgehog.Internal.Property

Methods

emptyPropertyT m a Source #

(<|>)PropertyT m a → PropertyT m a → PropertyT m a Source #

somePropertyT m a → PropertyT m [a] Source #

manyPropertyT m a → PropertyT m [a] Source #

Alternative m ⇒ Alternative (TreeT m) 
Instance details

Defined in Hedgehog.Internal.Tree

Methods

emptyTreeT m a Source #

(<|>)TreeT m a → TreeT m a → TreeT m a Source #

someTreeT m a → TreeT m [a] Source #

manyTreeT m a → TreeT m [a] Source #

Alternative f ⇒ Alternative (Yoneda f) 
Instance details

Defined in Data.Functor.Yoneda

Methods

empty ∷ Yoneda f a Source #

(<|>) ∷ Yoneda f a → Yoneda f a → Yoneda f a Source #

some ∷ Yoneda f a → Yoneda f [a] Source #

many ∷ Yoneda f a → Yoneda f [a] Source #

Alternative (ReifiedFold s) 
Instance details

Defined in Control.Lens.Reified

Methods

empty ∷ ReifiedFold s a Source #

(<|>) ∷ ReifiedFold s a → ReifiedFold s a → ReifiedFold s a Source #

some ∷ ReifiedFold s a → ReifiedFold s [a] Source #

many ∷ ReifiedFold s a → ReifiedFold s [a] Source #

(Monad m, Functor m) ⇒ Alternative (ListT m) 
Instance details

Defined in ListT

Methods

empty ∷ ListT m a Source #

(<|>) ∷ ListT m a → ListT m a → ListT m a Source #

some ∷ ListT m a → ListT m [a] Source #

many ∷ ListT m a → ListT m [a] Source #

Alternative m ⇒ Alternative (ResourceT m) 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

empty ∷ ResourceT m a Source #

(<|>) ∷ ResourceT m a → ResourceT m a → ResourceT m a Source #

some ∷ ResourceT m a → ResourceT m [a] Source #

many ∷ ResourceT m a → ResourceT m [a] Source #

Alternative f ⇒ Alternative (Lift f)

A combination is Pure only either part is.

Instance details

Defined in Control.Applicative.Lift

Methods

emptyLift f a Source #

(<|>)Lift f a → Lift f a → Lift f a Source #

someLift f a → Lift f [a] Source #

manyLift f a → Lift f [a] Source #

(Functor m, Monad m) ⇒ Alternative (MaybeT m) 
Instance details

Defined in Control.Monad.Trans.Maybe

Methods

emptyMaybeT m a Source #

(<|>)MaybeT m a → MaybeT m a → MaybeT m a Source #

someMaybeT m a → MaybeT m [a] Source #

manyMaybeT m a → MaybeT m [a] Source #

Alternative f ⇒ Alternative (WrappedFoldable f) 
Instance details

Defined in Witherable

(ArrowZero a, ArrowPlus a) ⇒ Alternative (WrappedArrow a b)

Since: base-2.1

Instance details

Defined in Control.Applicative

Methods

emptyWrappedArrow a b a0 Source #

(<|>)WrappedArrow a b a0 → WrappedArrow a b a0 → WrappedArrow a b a0 Source #

someWrappedArrow a b a0 → WrappedArrow a b [a0] Source #

manyWrappedArrow a b a0 → WrappedArrow a b [a0] Source #

Alternative m ⇒ Alternative (Kleisli m a)

Since: base-4.14.0.0

Instance details

Defined in Control.Arrow

Methods

emptyKleisli m a a0 Source #

(<|>)Kleisli m a a0 → Kleisli m a a0 → Kleisli m a a0 Source #

someKleisli m a a0 → Kleisli m a [a0] Source #

manyKleisli m a a0 → Kleisli m a [a0] Source #

Alternative f ⇒ Alternative (Ap f)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

emptyAp f a Source #

(<|>)Ap f a → Ap f a → Ap f a Source #

someAp f a → Ap f [a] Source #

manyAp f a → Ap f [a] Source #

Alternative f ⇒ Alternative (Alt f)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

emptyAlt f a Source #

(<|>)Alt f a → Alt f a → Alt f a Source #

someAlt f a → Alt f [a] Source #

manyAlt f a → Alt f [a] Source #

(Generic1 f, Alternative (Rep1 f)) ⇒ Alternative (Generically1 f)

Since: base-4.17.0.0

Instance details

Defined in GHC.Generics

Alternative f ⇒ Alternative (Rec1 f)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

emptyRec1 f a Source #

(<|>)Rec1 f a → Rec1 f a → Rec1 f a Source #

someRec1 f a → Rec1 f [a] Source #

manyRec1 f a → Rec1 f [a] Source #

(Functor f, MonadPlus m) ⇒ Alternative (FreeT f m) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

emptyFreeT f m a Source #

(<|>)FreeT f m a → FreeT f m a → FreeT f m a Source #

someFreeT f m a → FreeT f m [a] Source #

manyFreeT f m a → FreeT f m [a] Source #

Alternative m ⇒ Alternative (RenameT ren m) Source # 
Instance details

Defined in PlutusCore.Rename.Monad

Methods

emptyRenameT ren m a Source #

(<|>)RenameT ren m a → RenameT ren m a → RenameT ren m a Source #

someRenameT ren m a → RenameT ren m [a] Source #

manyRenameT ren m a → RenameT ren m [a] Source #

(Profunctor p, ArrowPlus p) ⇒ Alternative (Closure p a) 
Instance details

Defined in Data.Profunctor.Closed

Methods

emptyClosure p a a0 Source #

(<|>)Closure p a a0 → Closure p a a0 → Closure p a a0 Source #

someClosure p a a0 → Closure p a [a0] Source #

manyClosure p a a0 → Closure p a [a0] Source #

(Profunctor p, ArrowPlus p) ⇒ Alternative (Tambara p a) 
Instance details

Defined in Data.Profunctor.Strong

Methods

emptyTambara p a a0 Source #

(<|>)Tambara p a a0 → Tambara p a a0 → Tambara p a a0 Source #

someTambara p a a0 → Tambara p a [a0] Source #

manyTambara p a a0 → Tambara p a [a0] Source #

Alternative f ⇒ Alternative (Backwards f)

Try alternatives in the same order as f.

Instance details

Defined in Control.Applicative.Backwards

Methods

emptyBackwards f a Source #

(<|>)Backwards f a → Backwards f a → Backwards f a Source #

someBackwards f a → Backwards f [a] Source #

manyBackwards f a → Backwards f [a] Source #

(Monoid w, Functor m, MonadPlus m) ⇒ Alternative (AccumT w m) 
Instance details

Defined in Control.Monad.Trans.Accum

Methods

emptyAccumT w m a Source #

(<|>)AccumT w m a → AccumT w m a → AccumT w m a Source #

someAccumT w m a → AccumT w m [a] Source #

manyAccumT w m a → AccumT w m [a] Source #

(Functor m, Monad m, Monoid e) ⇒ Alternative (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

emptyExceptT e m a Source #

(<|>)ExceptT e m a → ExceptT e m a → ExceptT e m a Source #

someExceptT e m a → ExceptT e m [a] Source #

manyExceptT e m a → ExceptT e m [a] Source #

Alternative m ⇒ Alternative (IdentityT m) 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

emptyIdentityT m a Source #

(<|>)IdentityT m a → IdentityT m a → IdentityT m a Source #

someIdentityT m a → IdentityT m [a] Source #

manyIdentityT m a → IdentityT m [a] Source #

Alternative m ⇒ Alternative (ReaderT r m) 
Instance details

Defined in Control.Monad.Trans.Reader

Methods

emptyReaderT r m a Source #

(<|>)ReaderT r m a → ReaderT r m a → ReaderT r m a Source #

someReaderT r m a → ReaderT r m [a] Source #

manyReaderT r m a → ReaderT r m [a] Source #

(Functor m, MonadPlus m) ⇒ Alternative (SelectT r m) 
Instance details

Defined in Control.Monad.Trans.Select

Methods

emptySelectT r m a Source #

(<|>)SelectT r m a → SelectT r m a → SelectT r m a Source #

someSelectT r m a → SelectT r m [a] Source #

manySelectT r m a → SelectT r m [a] Source #

(Functor m, MonadPlus m) ⇒ Alternative (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Lazy

Methods

emptyStateT s m a Source #

(<|>)StateT s m a → StateT s m a → StateT s m a Source #

someStateT s m a → StateT s m [a] Source #

manyStateT s m a → StateT s m [a] Source #

(Functor m, MonadPlus m) ⇒ Alternative (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Strict

Methods

emptyStateT s m a Source #

(<|>)StateT s m a → StateT s m a → StateT s m a Source #

someStateT s m a → StateT s m [a] Source #

manyStateT s m a → StateT s m [a] Source #

(Functor m, MonadPlus m) ⇒ Alternative (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.CPS

Methods

emptyWriterT w m a Source #

(<|>)WriterT w m a → WriterT w m a → WriterT w m a Source #

someWriterT w m a → WriterT w m [a] Source #

manyWriterT w m a → WriterT w m [a] Source #

(Monoid w, Alternative m) ⇒ Alternative (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.Lazy

Methods

emptyWriterT w m a Source #

(<|>)WriterT w m a → WriterT w m a → WriterT w m a Source #

someWriterT w m a → WriterT w m [a] Source #

manyWriterT w m a → WriterT w m [a] Source #

(Monoid w, Alternative m) ⇒ Alternative (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

Methods

emptyWriterT w m a Source #

(<|>)WriterT w m a → WriterT w m a → WriterT w m a Source #

someWriterT w m a → WriterT w m [a] Source #

manyWriterT w m a → WriterT w m [a] Source #

Alternative f ⇒ Alternative (Reverse f)

Derived instance.

Instance details

Defined in Data.Functor.Reverse

Methods

emptyReverse f a Source #

(<|>)Reverse f a → Reverse f a → Reverse f a Source #

someReverse f a → Reverse f [a] Source #

manyReverse f a → Reverse f [a] Source #

(Alternative f, Alternative g) ⇒ Alternative (Product f g)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

emptyProduct f g a Source #

(<|>)Product f g a → Product f g a → Product f g a Source #

someProduct f g a → Product f g [a] Source #

manyProduct f g a → Product f g [a] Source #

(Alternative f, Alternative g) ⇒ Alternative (f :*: g)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

empty ∷ (f :*: g) a Source #

(<|>) ∷ (f :*: g) a → (f :*: g) a → (f :*: g) a Source #

some ∷ (f :*: g) a → (f :*: g) [a] Source #

many ∷ (f :*: g) a → (f :*: g) [a] Source #

(Ord e, Stream s) ⇒ Alternative (ParsecT e s m)

empty is a parser that fails without consuming input.

Instance details

Defined in Text.Megaparsec.Internal

Methods

emptyParsecT e s m a Source #

(<|>)ParsecT e s m a → ParsecT e s m a → ParsecT e s m a Source #

someParsecT e s m a → ParsecT e s m [a] Source #

manyParsecT e s m a → ParsecT e s m [a] Source #

Alternative f ⇒ Alternative (Star f a) 
Instance details

Defined in Data.Profunctor.Types

Methods

emptyStar f a a0 Source #

(<|>)Star f a a0 → Star f a a0 → Star f a a0 Source #

someStar f a a0 → Star f a [a0] Source #

manyStar f a a0 → Star f a [a0] Source #

(Alternative f, Applicative g) ⇒ Alternative (Compose f g)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

emptyCompose f g a Source #

(<|>)Compose f g a → Compose f g a → Compose f g a Source #

someCompose f g a → Compose f g [a] Source #

manyCompose f g a → Compose f g [a] Source #

(Alternative f, Applicative g) ⇒ Alternative (f :.: g)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

empty ∷ (f :.: g) a Source #

(<|>) ∷ (f :.: g) a → (f :.: g) a → (f :.: g) a Source #

some ∷ (f :.: g) a → (f :.: g) [a] Source #

many ∷ (f :.: g) a → (f :.: g) [a] Source #

Alternative f ⇒ Alternative (M1 i c f)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

emptyM1 i c f a Source #

(<|>)M1 i c f a → M1 i c f a → M1 i c f a Source #

someM1 i c f a → M1 i c f [a] Source #

manyM1 i c f a → M1 i c f [a] Source #

Alternative m ⇒ Alternative (NormalizeTypeT m tyname uni ann) Source # 
Instance details

Defined in PlutusCore.Normalize.Internal

Methods

emptyNormalizeTypeT m tyname uni ann a Source #

(<|>)NormalizeTypeT m tyname uni ann a → NormalizeTypeT m tyname uni ann a → NormalizeTypeT m tyname uni ann a Source #

someNormalizeTypeT m tyname uni ann a → NormalizeTypeT m tyname uni ann [a] Source #

manyNormalizeTypeT m tyname uni ann a → NormalizeTypeT m tyname uni ann [a] Source #

(Functor m, MonadPlus m) ⇒ Alternative (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.RWS.CPS

Methods

emptyRWST r w s m a Source #

(<|>)RWST r w s m a → RWST r w s m a → RWST r w s m a Source #

someRWST r w s m a → RWST r w s m [a] Source #

manyRWST r w s m a → RWST r w s m [a] Source #

(Monoid w, Functor m, MonadPlus m) ⇒ Alternative (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.RWS.Lazy

Methods

emptyRWST r w s m a Source #

(<|>)RWST r w s m a → RWST r w s m a → RWST r w s m a Source #

someRWST r w s m a → RWST r w s m [a] Source #

manyRWST r w s m a → RWST r w s m [a] Source #

(Monoid w, Functor m, MonadPlus m) ⇒ Alternative (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.RWS.Strict

Methods

emptyRWST r w s m a Source #

(<|>)RWST r w s m a → RWST r w s m a → RWST r w s m a Source #

someRWST r w s m a → RWST r w s m [a] Source #

manyRWST r w s m a → RWST r w s m [a] Source #

class (Typeable e, Show e) ⇒ Exception e Source #

Any type that you wish to throw or catch as an exception must be an instance of the Exception class. The simplest case is a new exception type directly below the root:

data MyException = ThisException | ThatException
    deriving Show

instance Exception MyException

The default method definitions in the Exception class do what we need in this case. You can now throw and catch ThisException and ThatException as exceptions:

*Main> throw ThisException `catch` \e -> putStrLn ("Caught " ++ show (e :: MyException))
Caught ThisException

In more complicated examples, you may wish to define a whole hierarchy of exceptions:

---------------------------------------------------------------------
-- Make the root exception type for all the exceptions in a compiler

data SomeCompilerException = forall e . Exception e => SomeCompilerException e

instance Show SomeCompilerException where
    show (SomeCompilerException e) = show e

instance Exception SomeCompilerException

compilerExceptionToException :: Exception e => e -> SomeException
compilerExceptionToException = toException . SomeCompilerException

compilerExceptionFromException :: Exception e => SomeException -> Maybe e
compilerExceptionFromException x = do
    SomeCompilerException a <- fromException x
    cast a

---------------------------------------------------------------------
-- Make a subhierarchy for exceptions in the frontend of the compiler

data SomeFrontendException = forall e . Exception e => SomeFrontendException e

instance Show SomeFrontendException where
    show (SomeFrontendException e) = show e

instance Exception SomeFrontendException where
    toException = compilerExceptionToException
    fromException = compilerExceptionFromException

frontendExceptionToException :: Exception e => e -> SomeException
frontendExceptionToException = toException . SomeFrontendException

frontendExceptionFromException :: Exception e => SomeException -> Maybe e
frontendExceptionFromException x = do
    SomeFrontendException a <- fromException x
    cast a

---------------------------------------------------------------------
-- Make an exception type for a particular frontend compiler exception

data MismatchedParentheses = MismatchedParentheses
    deriving Show

instance Exception MismatchedParentheses where
    toException   = frontendExceptionToException
    fromException = frontendExceptionFromException

We can now catch a MismatchedParentheses exception as MismatchedParentheses, SomeFrontendException or SomeCompilerException, but not other types, e.g. IOException:

*Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: MismatchedParentheses))
Caught MismatchedParentheses
*Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: SomeFrontendException))
Caught MismatchedParentheses
*Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: SomeCompilerException))
Caught MismatchedParentheses
*Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: IOException))
*** Exception: MismatchedParentheses

Instances

Instances details
Exception AesonException 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

toException ∷ AesonException → SomeException Source #

fromExceptionSomeExceptionMaybe AesonException Source #

displayException ∷ AesonException → String Source #

Exception NestedAtomically

Since: base-4.0

Instance details

Defined in Control.Exception.Base

Exception NoMatchingContinuationPrompt

Since: base-4.18

Instance details

Defined in Control.Exception.Base

Exception NoMethodError

Since: base-4.0

Instance details

Defined in Control.Exception.Base

Exception NonTermination

Since: base-4.0

Instance details

Defined in Control.Exception.Base

Exception PatternMatchFail

Since: base-4.0

Instance details

Defined in Control.Exception.Base

Exception RecConError

Since: base-4.0

Instance details

Defined in Control.Exception.Base

Exception RecSelError

Since: base-4.0

Instance details

Defined in Control.Exception.Base

Exception RecUpdError

Since: base-4.0

Instance details

Defined in Control.Exception.Base

Exception TypeError

Since: base-4.9.0.0

Instance details

Defined in Control.Exception.Base

Exception Void

Since: base-4.8.0.0

Instance details

Defined in GHC.Exception.Type

Exception ErrorCall

Since: base-4.0.0.0

Instance details

Defined in GHC.Exception

Exception ArithException

Since: base-4.0.0.0

Instance details

Defined in GHC.Exception.Type

Exception SomeException

Since: base-3.0

Instance details

Defined in GHC.Exception.Type

Exception AllocationLimitExceeded

Since: base-4.8.0.0

Instance details

Defined in GHC.IO.Exception

Exception ArrayException

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Exception AssertionFailed

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Exception AsyncException

Since: base-4.7.0.0

Instance details

Defined in GHC.IO.Exception

Exception BlockedIndefinitelyOnMVar

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Exception BlockedIndefinitelyOnSTM

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Exception CompactionFailed

Since: base-4.10.0.0

Instance details

Defined in GHC.IO.Exception

Exception Deadlock

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Exception ExitCode

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Exception FixIOException

Since: base-4.11.0.0

Instance details

Defined in GHC.IO.Exception

Exception IOException

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Exception SomeAsyncException

Since: base-4.7.0.0

Instance details

Defined in GHC.IO.Exception

Exception ASCII7_Invalid 
Instance details

Defined in Basement.String.Encoding.ASCII7

Methods

toException ∷ ASCII7_Invalid → SomeException Source #

fromExceptionSomeExceptionMaybe ASCII7_Invalid Source #

displayException ∷ ASCII7_Invalid → String Source #

Exception ISO_8859_1_Invalid 
Instance details

Defined in Basement.String.Encoding.ISO_8859_1

Methods

toException ∷ ISO_8859_1_Invalid → SomeException Source #

fromExceptionSomeExceptionMaybe ISO_8859_1_Invalid Source #

displayException ∷ ISO_8859_1_Invalid → String Source #

Exception UTF16_Invalid 
Instance details

Defined in Basement.String.Encoding.UTF16

Methods

toException ∷ UTF16_Invalid → SomeException Source #

fromExceptionSomeExceptionMaybe UTF16_Invalid Source #

displayException ∷ UTF16_Invalid → String Source #

Exception UTF32_Invalid 
Instance details

Defined in Basement.String.Encoding.UTF32

Methods

toException ∷ UTF32_Invalid → SomeException Source #

fromExceptionSomeExceptionMaybe UTF32_Invalid Source #

displayException ∷ UTF32_Invalid → String Source #

Exception BimapException 
Instance details

Defined in Data.Bimap

Methods

toException ∷ BimapException → SomeException Source #

fromExceptionSomeExceptionMaybe BimapException Source #

displayException ∷ BimapException → String Source #

Exception DeserialiseFailure 
Instance details

Defined in Codec.CBOR.Read

Exception CryptoError 
Instance details

Defined in Crypto.Error.Types

Exception DecodeException 
Instance details

Defined in Flat.Decoder.Types

Exception HandlingException 
Instance details

Defined in Control.Lens.Internal.Exception

Methods

toException ∷ HandlingException → SomeException Source #

fromExceptionSomeExceptionMaybe HandlingException Source #

displayException ∷ HandlingException → String Source #

Exception InvalidPosException 
Instance details

Defined in Text.Megaparsec.Pos

Exception FreeVariableError Source # 
Instance details

Defined in PlutusCore.DeBruijn.Internal

Exception ApplyProgramError Source # 
Instance details

Defined in PlutusCore.Error

Exception CostModelApplyError Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostModelInterface

Exception BuiltinErrorCall Source # 
Instance details

Defined in PlutusCore.Examples.Builtins

Exception InvalidAccess 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

toException ∷ InvalidAccess → SomeException Source #

fromExceptionSomeExceptionMaybe InvalidAccess Source #

displayException ∷ InvalidAccess → String Source #

Exception ResourceCleanupException 
Instance details

Defined in Control.Monad.Trans.Resource.Internal

Methods

toException ∷ ResourceCleanupException → SomeException Source #

fromExceptionSomeExceptionMaybe ResourceCleanupException Source #

displayException ∷ ResourceCleanupException → String Source #

Exception UnicodeException 
Instance details

Defined in Data.Text.Encoding.Error

Exception (UniqueError SrcSpan) Source # 
Instance details

Defined in PlutusCore.Error

(Show s, Show (Token s), Show e, ShowErrorComponent e, VisualStream s, Typeable s, Typeable e) ⇒ Exception (ParseError s e) 
Instance details

Defined in Text.Megaparsec.Error

(Show s, Show (Token s), Show e, ShowErrorComponent e, VisualStream s, TraversableStream s, Typeable s, Typeable e) ⇒ Exception (ParseErrorBundle s e) 
Instance details

Defined in Text.Megaparsec.Error

(PrettyPlc cause, PrettyPlc err, Typeable cause, Typeable err) ⇒ Exception (ErrorWithCause err cause) Source # 
Instance details

Defined in PlutusCore.Evaluation.ErrorWithCause

(Reifies s (SomeExceptionMaybe a), Typeable a, Typeable s, Typeable m) ⇒ Exception (Handling a s m) 
Instance details

Defined in Control.Lens.Internal.Exception

Methods

toException ∷ Handling a s m → SomeException Source #

fromExceptionSomeExceptionMaybe (Handling a s m) Source #

displayException ∷ Handling a s m → String Source #

newtype PairT b f a Source #

Constructors

PairT 

Fields

Instances

Instances details
Functor f ⇒ Functor (PairT b f) Source # 
Instance details

Defined in PlutusPrelude

Methods

fmap ∷ (a → b0) → PairT b f a → PairT b f b0 Source #

(<$) ∷ a → PairT b f b0 → PairT b f a Source #

class a ~R# b ⇒ Coercible (a ∷ k) (b ∷ k) Source #

Coercible is a two-parameter class that has instances for types a and b if the compiler can infer that they have the same representation. This class does not have regular instances; instead they are created on-the-fly during type-checking. Trying to manually declare an instance of Coercible is an error.

Nevertheless one can pretend that the following three kinds of instances exist. First, as a trivial base-case:

instance Coercible a a

Furthermore, for every type constructor there is an instance that allows to coerce under the type constructor. For example, let D be a prototypical type constructor (data or newtype) with three type arguments, which have roles nominal, representational resp. phantom. Then there is an instance of the form

instance Coercible b b' => Coercible (D a b c) (D a b' c')

Note that the nominal type arguments are equal, the representational type arguments can differ, but need to have a Coercible instance themself, and the phantom type arguments can be changed arbitrarily.

The third kind of instance exists for every newtype NT = MkNT T and comes in two variants, namely

instance Coercible a T => Coercible a NT
instance Coercible T b => Coercible NT b

This instance is only usable if the constructor MkNT is in scope.

If, as a library author of a type constructor like Set a, you want to prevent a user of your module to write coerce :: Set T -> Set NT, you need to set the role of Set's type parameter to nominal, by writing

type role Set nominal

For more details about this feature, please refer to Safe Coercions by Joachim Breitner, Richard A. Eisenberg, Simon Peyton Jones and Stephanie Weirich.

Since: ghc-prim-0.4.0

class Typeable (a ∷ k) Source #

The class Typeable allows a concrete representation of a type to be calculated.

Minimal complete definition

typeRep#

Lens

type Lens' s a = Lens s s a a #

lens ∷ (s → a) → (s → b → t) → Lens s t a b #

(^.) ∷ s → Getting a s a → a #

viewMonadReader s m ⇒ Getting a s a → m a #

(.~) ∷ ASetter s t a b → b → s → t #

set ∷ ASetter s t a b → b → s → t #

(%~) ∷ ASetter s t a b → (a → b) → s → t #

over ∷ ASetter s t a b → (a → b) → s → t #

(<^>) ∷ Fold s a → Fold s a → Fold s a infixr 6 Source #

Compose two folds to make them run in parallel. The results are concatenated.

Debugging

traceShowIdShow a ⇒ a → a Source #

Like traceShow but returns the shown value instead of a third value.

>>> traceShowId (1+2+3, "hello" ++ "world")
(6,"helloworld")
(6,"helloworld")

Since: base-4.7.0.0

traceString → a → a Source #

The trace function outputs the trace message given as its first argument, before returning the second argument as its result.

For example, this returns the value of f x and outputs the message to stderr. Depending on your terminal (settings), they may or may not be mixed.

>>> let x = 123; f = show
>>> trace ("calling f with x = " ++ show x) (f x)
calling f with x = 123
"123"

The trace function should only be used for debugging, or for monitoring execution. The function is not referentially transparent: its type indicates that it is a pure function but it has the side effect of outputting the trace message.

Reexports from Control.Composition

(.*) ∷ (c → d) → (a → b → c) → a → b → d infixr 8 Source #

Custom functions

(<<$>>) ∷ (Functor f1, Functor f2) ⇒ (a → b) → f1 (f2 a) → f1 (f2 b) infixl 4 Source #

(<<*>>) ∷ (Applicative f1, Applicative f2) ⇒ f1 (f2 (a → b)) → f1 (f2 a) → f1 (f2 b) infixl 4 Source #

mtraverse ∷ (Monad m, Traversable m, Applicative f) ⇒ (a → f (m b)) → m a → f (m b) Source #

foldMapM ∷ (Foldable f, Monad m, Monoid b) ⇒ (a → m b) → f a → m b Source #

Fold a monadic function over a Foldable. The monadic version of foldMap.

reoption ∷ (Foldable f, Alternative g) ⇒ f a → g a Source #

This function generalizes eitherToMaybe, eitherToList, listToMaybe and other such functions.

enumerate ∷ (Enum a, Bounded a) ⇒ [a] Source #

Enumerate all the values of an Enum, from minBound to maxBound.

enumerate == [False, True]

tabulateArray ∷ (Bounded i, Enum i, Ix i) ⇒ (i → a) → Array i a Source #

Basically a Data.Functor.Representable instance for Array. We can't provide an actual instance because of the Distributive superclass: Array i is not Distributive unless we assume that indices in an array range over the entirety of i.

(?)Alternative f ⇒ Bool → a → f a infixr 2 Source #

b ? x is equal to pure x whenever b holds and is empty otherwise.

ensureAlternative f ⇒ (a → Bool) → a → f a Source #

ensure p x is equal to pure x whenever p x holds and is empty otherwise.

asksMMonadReader r m ⇒ (r → m a) → m a Source #

A monadic version of asks.

timesANatural → (a → a) → a → a Source #

function recursively applied N times

Pretty-printing

data Doc ann Source #

The abstract data type Doc ann represents pretty documents that have been annotated with data of type ann.

More specifically, a value of type Doc represents a non-empty set of possible layouts of a document. The layout functions select one of these possibilities, taking into account things like the width of the output document.

The annotation is an arbitrary piece of data associated with (part of) a document. Annotations may be used by the rendering backends in order to display output differently, such as

  • color information (e.g. when rendering to the terminal)
  • mouseover text (e.g. when rendering to rich HTML)
  • whether to show something or not (to allow simple or detailed versions)

The simplest way to display a Doc is via the Show class.

>>> putStrLn (show (vsep ["hello", "world"]))
hello
world

Instances

Instances details
Functor Doc

Alter the document’s annotations.

This instance makes Doc more flexible (because it can be used in Functor-polymorphic values), but fmap is much less readable compared to using reAnnotate in code that only works for Doc anyway. Consider using the latter when the type does not matter.

Instance details

Defined in Prettyprinter.Internal

Methods

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

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

IsString (Doc ann)
>>> pretty ("hello\nworld")
hello
world

This instance uses the Pretty Doc instance, and uses the same newline to line conversion.

Instance details

Defined in Prettyprinter.Internal

Methods

fromStringStringDoc ann Source #

Monoid (Doc ann)
mempty = emptyDoc
mconcat = hcat
>>> mappend "hello" "world" :: Doc ann
helloworld
Instance details

Defined in Prettyprinter.Internal

Methods

memptyDoc ann Source #

mappendDoc ann → Doc ann → Doc ann Source #

mconcat ∷ [Doc ann] → Doc ann Source #

Semigroup (Doc ann)
x <> y = hcat [x, y]
>>> "hello" <> "world" :: Doc ann
helloworld
Instance details

Defined in Prettyprinter.Internal

Methods

(<>)Doc ann → Doc ann → Doc ann Source #

sconcatNonEmpty (Doc ann) → Doc ann Source #

stimesIntegral b ⇒ b → Doc ann → Doc ann Source #

Generic (Doc ann) 
Instance details

Defined in Prettyprinter.Internal

Associated Types

type Rep (Doc ann) ∷ TypeType Source #

Methods

fromDoc ann → Rep (Doc ann) x Source #

toRep (Doc ann) x → Doc ann Source #

Show (Doc ann)

(show doc) prettyprints document doc with defaultLayoutOptions, ignoring all annotations.

Instance details

Defined in Prettyprinter.Internal

Methods

showsPrecIntDoc ann → ShowS Source #

showDoc ann → String Source #

showList ∷ [Doc ann] → ShowS Source #

type Rep (Doc ann) 
Instance details

Defined in Prettyprinter.Internal

type Rep (Doc ann) = D1 ('MetaData "Doc" "Prettyprinter.Internal" "prettyprinter-1.7.1-60yVE7QePDs8FHIPsacPFF" 'False) (((C1 ('MetaCons "Fail" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "Empty" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "Char" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Char)))) :+: (C1 ('MetaCons "Text" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :+: (C1 ('MetaCons "Line" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "FlatAlt" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann)) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann)))))) :+: ((C1 ('MetaCons "Cat" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann)) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann))) :+: (C1 ('MetaCons "Nest" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann))) :+: C1 ('MetaCons "Union" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann)) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann))))) :+: ((C1 ('MetaCons "Column" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (IntDoc ann))) :+: C1 ('MetaCons "WithPageWidth" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PageWidthDoc ann)))) :+: (C1 ('MetaCons "Nesting" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (IntDoc ann))) :+: C1 ('MetaCons "Annotated" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ann) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann)))))))

newtype ShowPretty a Source #

A newtype wrapper around a whose point is to provide a Show instance for anything that has a Pretty instance.

Constructors

ShowPretty 

Fields

Instances

Instances details
Pretty a ⇒ Show (ShowPretty a) Source # 
Instance details

Defined in PlutusPrelude

Eq a ⇒ Eq (ShowPretty a) Source # 
Instance details

Defined in PlutusPrelude

Methods

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

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

class Pretty a where Source #

Overloaded conversion to Doc.

Laws:

  1. output should be pretty. :-)

Minimal complete definition

pretty

Methods

pretty ∷ a → Doc ann Source #

>>> pretty 1 <+> pretty "hello" <+> pretty 1.234
1 hello 1.234

prettyList ∷ [a] → Doc ann Source #

prettyList is only used to define the instance Pretty a => Pretty [a]. In normal circumstances only the pretty function is used.

>>> prettyList [1, 23, 456]
[1, 23, 456]

Instances

Instances details
Pretty Void

Finding a good example for printing something that does not exist is hard, so here is an example of printing a list full of nothing.

>>> pretty ([] :: [Void])
[]
Instance details

Defined in Prettyprinter.Internal

Methods

prettyVoidDoc ann Source #

prettyList ∷ [Void] → Doc ann Source #

Pretty Int16 
Instance details

Defined in Prettyprinter.Internal

Methods

prettyInt16Doc ann Source #

prettyList ∷ [Int16] → Doc ann Source #

Pretty Int32 
Instance details

Defined in Prettyprinter.Internal

Methods

prettyInt32Doc ann Source #

prettyList ∷ [Int32] → Doc ann Source #

Pretty Int64 
Instance details

Defined in Prettyprinter.Internal

Methods

prettyInt64Doc ann Source #

prettyList ∷ [Int64] → Doc ann Source #

Pretty Int8 
Instance details

Defined in Prettyprinter.Internal

Methods

prettyInt8Doc ann Source #

prettyList ∷ [Int8] → Doc ann Source #

Pretty Word16 
Instance details

Defined in Prettyprinter.Internal

Methods

prettyWord16Doc ann Source #

prettyList ∷ [Word16] → Doc ann Source #

Pretty Word32 
Instance details

Defined in Prettyprinter.Internal

Methods

prettyWord32Doc ann Source #

prettyList ∷ [Word32] → Doc ann Source #

Pretty Word64 
Instance details

Defined in Prettyprinter.Internal

Methods

prettyWord64Doc ann Source #

prettyList ∷ [Word64] → Doc ann Source #

Pretty Word8 
Instance details

Defined in Prettyprinter.Internal

Methods

prettyWord8Doc ann Source #

prettyList ∷ [Word8] → Doc ann Source #

Pretty SourcePos Source # 
Instance details

Defined in PlutusCore.Error

Methods

prettySourcePosDoc ann Source #

prettyList ∷ [SourcePos] → Doc ann Source #

Pretty DeserialiseFailureInfo Source # 
Instance details

Defined in Codec.Extras.SerialiseViaFlat

Pretty DeserialiseFailureReason Source # 
Instance details

Defined in Codec.Extras.SerialiseViaFlat

Pretty Ann Source # 
Instance details

Defined in PlutusCore.Annotation

Methods

prettyAnnDoc ann Source #

prettyList ∷ [Ann] → Doc ann Source #

Pretty SrcSpan Source # 
Instance details

Defined in PlutusCore.Annotation

Methods

prettySrcSpanDoc ann Source #

prettyList ∷ [SrcSpan] → Doc ann Source #

Pretty SrcSpans Source # 
Instance details

Defined in PlutusCore.Annotation

Methods

prettySrcSpansDoc ann Source #

prettyList ∷ [SrcSpans] → Doc ann Source #

Pretty Param Source # 
Instance details

Defined in PlutusCore.Arity

Methods

prettyParamDoc ann Source #

prettyList ∷ [Param] → Doc ann Source #

Pretty BuiltinError Source # 
Instance details

Defined in PlutusCore.Builtin.Result

Methods

prettyBuiltinErrorDoc ann Source #

prettyList ∷ [BuiltinError] → Doc ann Source #

Pretty UnliftingError Source # 
Instance details

Defined in PlutusCore.Builtin.Result

Pretty UnliftingEvaluationError Source # 
Instance details

Defined in PlutusCore.Builtin.Result

Pretty NameAnn Source # 
Instance details

Defined in PlutusCore.Check.Scoping

Methods

prettyNameAnnDoc ann Source #

prettyList ∷ [NameAnn] → Doc ann Source #

Pretty ScopeError Source # 
Instance details

Defined in PlutusCore.Check.Scoping

Methods

prettyScopeErrorDoc ann Source #

prettyList ∷ [ScopeError] → Doc ann Source #

Pretty Element Source # 
Instance details

Defined in PlutusCore.Crypto.BLS12_381.G1

Methods

prettyElementDoc ann Source #

prettyList ∷ [Element] → Doc ann Source #

Pretty Element Source # 
Instance details

Defined in PlutusCore.Crypto.BLS12_381.G2

Methods

prettyElementDoc ann Source #

prettyList ∷ [Element] → Doc ann Source #

Pretty MlResult Source # 
Instance details

Defined in PlutusCore.Crypto.BLS12_381.Pairing

Methods

prettyMlResultDoc ann Source #

prettyList ∷ [MlResult] → Doc ann Source #

Pretty Data Source # 
Instance details

Defined in PlutusCore.Data

Methods

prettyDataDoc ann Source #

prettyList ∷ [Data] → Doc ann Source #

Pretty FreeVariableError Source # 
Instance details

Defined in PlutusCore.DeBruijn.Internal

Pretty Index Source # 
Instance details

Defined in PlutusCore.DeBruijn.Internal

Methods

prettyIndexDoc ann Source #

prettyList ∷ [Index] → Doc ann Source #

Pretty DefaultFun Source # 
Instance details

Defined in PlutusCore.Default.Builtins

Methods

prettyDefaultFunDoc ann Source #

prettyList ∷ [DefaultFun] → Doc ann Source #

Pretty ParserError Source # 
Instance details

Defined in PlutusCore.Error

Methods

prettyParserErrorDoc ann Source #

prettyList ∷ [ParserError] → Doc ann Source #

Pretty ParserErrorBundle Source # 
Instance details

Defined in PlutusCore.Error

Pretty CostModelApplyError Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostModelInterface

Pretty CostModelApplyWarn Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostModelInterface

Pretty ExBudget Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

Methods

prettyExBudgetDoc ann Source #

prettyList ∷ [ExBudget] → Doc ann Source #

Pretty ExRestrictingBudget Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

Pretty ExCPU Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Methods

prettyExCPUDoc ann Source #

prettyList ∷ [ExCPU] → Doc ann Source #

Pretty ExMemory Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Methods

prettyExMemoryDoc ann Source #

prettyList ∷ [ExMemory] → Doc ann Source #

Pretty ExtensionFun Source # 
Instance details

Defined in PlutusCore.Examples.Builtins

Methods

prettyExtensionFunDoc ann Source #

prettyList ∷ [ExtensionFun] → Doc ann Source #

Pretty Name Source # 
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Default

Methods

prettyNameDoc ann Source #

prettyList ∷ [Name] → Doc ann Source #

Pretty TyName Source # 
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Default

Methods

prettyTyNameDoc ann Source #

prettyList ∷ [TyName] → Doc ann Source #

Pretty Unique Source # 
Instance details

Defined in PlutusCore.Name.Unique

Methods

prettyUniqueDoc ann Source #

prettyList ∷ [Unique] → Doc ann Source #

Pretty Size Source # 
Instance details

Defined in PlutusCore.Size

Methods

prettySizeDoc ann Source #

prettyList ∷ [Size] → Doc ann Source #

Pretty Version Source # 
Instance details

Defined in PlutusCore.Version

Methods

prettyVersionDoc ann Source #

prettyList ∷ [Version] → Doc ann Source #

Pretty CountingSt Source # 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

Methods

prettyCountingStDoc ann Source #

prettyList ∷ [CountingSt] → Doc ann Source #

Pretty RestrictingSt Source # 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

Pretty CekUserError Source # 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Methods

prettyCekUserErrorDoc ann Source #

prettyList ∷ [CekUserError] → Doc ann Source #

Pretty Purity Source # 
Instance details

Defined in UntypedPlutusCore.Purity

Methods

prettyPurityDoc ann Source #

prettyList ∷ [Purity] → Doc ann Source #

Pretty Text

Automatically converts all newlines to line.

>>> pretty ("hello\nworld" :: Text)
hello
world

Note that line can be undone by group:

>>> group (pretty ("hello\nworld" :: Text))
hello world

Manually use hardline if you definitely want newlines.

Instance details

Defined in Prettyprinter.Internal

Methods

prettyTextDoc ann Source #

prettyList ∷ [Text] → Doc ann Source #

Pretty Text

(lazy Doc instance, identical to the strict version)

Instance details

Defined in Prettyprinter.Internal

Methods

prettyTextDoc ann Source #

prettyList ∷ [Text] → Doc ann Source #

Pretty Integer
>>> pretty (2^123 :: Integer)
10633823966279326983230456482242756608
Instance details

Defined in Prettyprinter.Internal

Methods

prettyIntegerDoc ann Source #

prettyList ∷ [Integer] → Doc ann Source #

Pretty Natural 
Instance details

Defined in Prettyprinter.Internal

Methods

prettyNaturalDoc ann Source #

prettyList ∷ [Natural] → Doc ann Source #

Pretty ()
>>> pretty ()
()

The argument is not used:

>>> pretty (error "Strict?" :: ())
()
Instance details

Defined in Prettyprinter.Internal

Methods

pretty ∷ () → Doc ann Source #

prettyList ∷ [()] → Doc ann Source #

Pretty Bool
>>> pretty True
True
Instance details

Defined in Prettyprinter.Internal

Methods

prettyBoolDoc ann Source #

prettyList ∷ [Bool] → Doc ann Source #

Pretty Char

Instead of (pretty 'n'), consider using line as a more readable alternative.

>>> pretty 'f' <> pretty 'o' <> pretty 'o'
foo
>>> pretty ("string" :: String)
string
Instance details

Defined in Prettyprinter.Internal

Methods

prettyCharDoc ann Source #

prettyList ∷ [Char] → Doc ann Source #

Pretty Double
>>> pretty (exp 1 :: Double)
2.71828182845904...
Instance details

Defined in Prettyprinter.Internal

Methods

prettyDoubleDoc ann Source #

prettyList ∷ [Double] → Doc ann Source #

Pretty Float
>>> pretty (pi :: Float)
3.1415927
Instance details

Defined in Prettyprinter.Internal

Methods

prettyFloatDoc ann Source #

prettyList ∷ [Float] → Doc ann Source #

Pretty Int
>>> pretty (123 :: Int)
123
Instance details

Defined in Prettyprinter.Internal

Methods

prettyIntDoc ann Source #

prettyList ∷ [Int] → Doc ann Source #

Pretty Word 
Instance details

Defined in Prettyprinter.Internal

Methods

prettyWordDoc ann Source #

prettyList ∷ [Word] → Doc ann Source #

Pretty a ⇒ Pretty (Identity a)
>>> pretty (Identity 1)
1
Instance details

Defined in Prettyprinter.Internal

Methods

prettyIdentity a → Doc ann Source #

prettyList ∷ [Identity a] → Doc ann Source #

Pretty a ⇒ Pretty (NonEmpty a) 
Instance details

Defined in Prettyprinter.Internal

Methods

prettyNonEmpty a → Doc ann Source #

prettyList ∷ [NonEmpty a] → Doc ann Source #

Pretty (BuiltinSemanticsVariant DefaultFun) Source # 
Instance details

Defined in PlutusCore.Default.Builtins

Pretty ann ⇒ Pretty (Kind ann) Source # 
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Default

Methods

prettyKind ann → Doc ann0 Source #

prettyList ∷ [Kind ann] → Doc ann0 Source #

Pretty a ⇒ Pretty (Normalized a) Source # 
Instance details

Defined in PlutusCore.Core.Type

Methods

prettyNormalized a → Doc ann Source #

prettyList ∷ [Normalized a] → Doc ann Source #

Pretty (DefaultUni a) Source #

This always pretty-prints parens around type applications (e.g. (list bool)) and doesn't pretty-print them otherwise (e.g. integer).

Instance details

Defined in PlutusCore.Default.Universe

Methods

prettyDefaultUni a → Doc ann Source #

prettyList ∷ [DefaultUni a] → Doc ann Source #

Pretty ann ⇒ Pretty (UniqueError ann) Source # 
Instance details

Defined in PlutusCore.Error

Methods

prettyUniqueError ann → Doc ann0 Source #

prettyList ∷ [UniqueError ann] → Doc ann0 Source #

PrettyClassic a ⇒ Pretty (EvaluationResult a) Source # 
Instance details

Defined in PlutusCore.Evaluation.Result

PrettyReadable a ⇒ Pretty (AsReadable a) Source # 
Instance details

Defined in PlutusCore.Pretty.Readable

Methods

prettyAsReadable a → Doc ann Source #

prettyList ∷ [AsReadable a] → Doc ann Source #

Pretty (SomeTypeIn DefaultUni) Source # 
Instance details

Defined in PlutusCore.Default.Universe

Pretty (SomeTypeIn uni) ⇒ Pretty (SomeTypeIn (Kinded uni)) Source # 
Instance details

Defined in PlutusCore.Pretty.PrettyConst

Methods

prettySomeTypeIn (Kinded uni) → Doc ann Source #

prettyList ∷ [SomeTypeIn (Kinded uni)] → Doc ann Source #

(Show fun, Ord fun) ⇒ Pretty (CekExTally fun) Source # 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

Methods

prettyCekExTally fun → Doc ann Source #

prettyList ∷ [CekExTally fun] → Doc ann Source #

(Show fun, Ord fun) ⇒ Pretty (TallyingSt fun) Source # 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

Methods

prettyTallyingSt fun → Doc ann Source #

prettyList ∷ [TallyingSt fun] → Doc ann Source #

Show fun ⇒ Pretty (ExBudgetCategory fun) Source # 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Methods

prettyExBudgetCategory fun → Doc ann Source #

prettyList ∷ [ExBudgetCategory fun] → Doc ann Source #

Pretty a ⇒ Pretty (Maybe a)

Ignore Nothings, print Just contents.

>>> pretty (Just True)
True
>>> braces (pretty (Nothing :: Maybe Bool))
{}
>>> pretty [Just 1, Nothing, Just 3, Nothing]
[1, 3]
Instance details

Defined in Prettyprinter.Internal

Methods

prettyMaybe a → Doc ann Source #

prettyList ∷ [Maybe a] → Doc ann Source #

Pretty a ⇒ Pretty [a]
>>> pretty [1,2,3]
[1, 2, 3]
Instance details

Defined in Prettyprinter.Internal

Methods

pretty ∷ [a] → Doc ann Source #

prettyList ∷ [[a]] → Doc ann Source #

(Pretty a, Pretty b) ⇒ Pretty (Either a b) Source # 
Instance details

Defined in PlutusPrelude

Methods

prettyEither a b → Doc ann Source #

prettyList ∷ [Either a b] → Doc ann Source #

(Pretty structural, Pretty operational) ⇒ Pretty (EvaluationError structural operational) Source # 
Instance details

Defined in PlutusCore.Evaluation.Error

Methods

prettyEvaluationError structural operational → Doc ann Source #

prettyList ∷ [EvaluationError structural operational] → Doc ann Source #

(Pretty err, Pretty cause) ⇒ Pretty (ErrorWithCause err cause) Source # 
Instance details

Defined in PlutusCore.Evaluation.ErrorWithCause

Methods

prettyErrorWithCause err cause → Doc ann Source #

prettyList ∷ [ErrorWithCause err cause] → Doc ann Source #

(Closed uni, Everywhere uni PrettyConst) ⇒ Pretty (ValueOf uni a) Source # 
Instance details

Defined in PlutusCore.Pretty.PrettyConst

Methods

prettyValueOf uni a → Doc ann Source #

prettyList ∷ [ValueOf uni a] → Doc ann Source #

DefaultPrettyBy config a ⇒ Pretty (AttachDefaultPrettyConfig config a) 
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyAttachDefaultPrettyConfig config a → Doc ann Source #

prettyList ∷ [AttachDefaultPrettyConfig config a] → Doc ann Source #

PrettyBy config a ⇒ Pretty (AttachPrettyConfig config a)
>>> data Cfg = Cfg
>>> data D = D
>>> instance PrettyBy Cfg D where prettyBy Cfg D = "D"
>>> pretty $ AttachPrettyConfig Cfg D
D
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyAttachPrettyConfig config a → Doc ann Source #

prettyList ∷ [AttachPrettyConfig config a] → Doc ann Source #

(Closed uni, Everywhere uni PrettyConst) ⇒ Pretty (Some (ValueOf uni)) Source # 
Instance details

Defined in PlutusCore.Pretty.PrettyConst

Methods

prettySome (ValueOf uni) → Doc ann Source #

prettyList ∷ [Some (ValueOf uni)] → Doc ann Source #

(Pretty a1, Pretty a2) ⇒ Pretty (a1, a2)
>>> pretty (123, "hello")
(123, hello)
Instance details

Defined in Prettyprinter.Internal

Methods

pretty ∷ (a1, a2) → Doc ann Source #

prettyList ∷ [(a1, a2)] → Doc ann Source #

Pretty a ⇒ Pretty (Const a b) 
Instance details

Defined in Prettyprinter.Internal

Methods

prettyConst a b → Doc ann Source #

prettyList ∷ [Const a b] → Doc ann Source #

(PrettyClassic tyname, PrettyParens (SomeTypeIn uni), Pretty ann) ⇒ Pretty (Type tyname uni ann) Source # 
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Default

Methods

prettyType tyname uni ann → Doc ann0 Source #

prettyList ∷ [Type tyname uni ann] → Doc ann0 Source #

Pretty (CekState uni fun ann) Source # 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.SteppableCek.Internal

Methods

prettyCekState uni fun ann → Doc ann0 Source #

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

(Pretty a1, Pretty a2, Pretty a3) ⇒ Pretty (a1, a2, a3)
>>> pretty (123, "hello", False)
(123, hello, False)
Instance details

Defined in Prettyprinter.Internal

Methods

pretty ∷ (a1, a2, a3) → Doc ann Source #

prettyList ∷ [(a1, a2, a3)] → Doc ann Source #

(PrettyClassic name, PrettyUni uni, Pretty fun, Pretty ann) ⇒ Pretty (Program name uni fun ann) Source # 
Instance details

Defined in UntypedPlutusCore.Core.Instance.Pretty.Default

Methods

prettyProgram name uni fun ann → Doc ann0 Source #

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

(PrettyClassic name, PrettyUni uni, Pretty fun, Pretty ann) ⇒ Pretty (Term name uni fun ann) Source # 
Instance details

Defined in UntypedPlutusCore.Core.Instance.Pretty.Default

Methods

prettyTerm name uni fun ann → Doc ann0 Source #

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

(PrettyClassic tyname, PrettyClassic name, PrettyUni uni, Pretty fun, Pretty ann) ⇒ Pretty (Program tyname name uni fun ann) Source # 
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Default

Methods

prettyProgram tyname name uni fun ann → Doc ann0 Source #

prettyList ∷ [Program tyname name uni fun ann] → Doc ann0 Source #

(PrettyClassic tyname, PrettyClassic name, PrettyUni uni, Pretty fun, Pretty ann) ⇒ Pretty (Term tyname name uni fun ann) Source # 
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Default

Methods

prettyTerm tyname name uni fun ann → Doc ann0 Source #

prettyList ∷ [Term tyname name uni fun ann] → Doc ann0 Source #

class PrettyBy config a where Source #

A class for pretty-printing values in a configurable manner.

A basic example:

>>> data Case = UpperCase | LowerCase
>>> data D = D
>>> instance PrettyBy Case D where prettyBy UpperCase D = "D"; prettyBy LowerCase D = "d"
>>> prettyBy UpperCase D
D
>>> prettyBy LowerCase D
d

The library provides instances for common types like Integer or Bool, so you can't define your own PrettyBy SomeConfig Integer instance. And for the same reason you should not define instances like PrettyBy SomeAnotherConfig a for universally quantified a, because such an instance would overlap with the existing ones. Take for example

>>> data ViaShow = ViaShow
>>> instance Show a => PrettyBy ViaShow a where prettyBy ViaShow = pretty . show

with such an instance prettyBy ViaShow (1 :: Int) throws an error about overlapping instances:

• Overlapping instances for PrettyBy ViaShow Int
    arising from a use of ‘prettyBy’
  Matching instances:
    instance PrettyDefaultBy config Int => PrettyBy config Int
    instance [safe] Show a => PrettyBy ViaShow a

There's a newtype provided specifically for the purpose of defining a PrettyBy instance for any a: PrettyAny. Read its docs for details on when you might want to use it.

The PrettyBy instance for common types is defined in a way that allows to override default pretty-printing behaviour, read the docs of HasPrettyDefaults for details.

Minimal complete definition

Nothing

Methods

prettyBy ∷ config → a → Doc ann Source #

Pretty-print a value of type a the way a config specifies it. The default implementation of prettyBy is in terms of pretty, defaultPrettyFunctorBy or defaultPrettyBifunctorBy depending on the kind of the data type that you're providing an instance for. For example, the default implementation of prettyBy for a monomorphic type is going to be "ignore the config and call pretty over the value":

>>> newtype N = N Int deriving newtype (Pretty)
>>> instance PrettyBy () N
>>> prettyBy () (N 42)
42

The default implementation of prettyBy for a Functor is going to be in terms of defaultPrettyFunctorBy:

>>> newtype N a = N a deriving stock (Functor) deriving newtype (Pretty)
>>> instance PrettyBy () a => PrettyBy () (N a)
>>> prettyBy () (N (42 :: Int))
42

It's fine for the data type to have a phantom parameter as long as the data type is still a Functor (i.e. the parameter has to be of kind Type). Then defaultPrettyFunctorBy is used again:

>>> newtype N a = N Int deriving stock (Functor) deriving newtype (Pretty)
>>> instance PrettyBy () (N b)
>>> prettyBy () (N 42)
42

If the data type has a single parameter of any other kind, then it's not a functor and so like in the monomorphic case pretty is used:

>>> newtype N (b :: Bool) = N Int deriving newtype (Pretty)
>>> instance PrettyBy () (N b)
>>> prettyBy () (N 42)
42

Same applies to a data type with two parameters: if both the parameters are of kind Type, then the data type is assumed to be a Bifunctor and hence defaultPrettyBifunctorBy is used. If the right parameter is of kind Type and the left parameter is of any other kind, then we fallback to assuming the data type is a Functor and defining prettyBy as defaultPrettyFunctorBy. If both the parameters are not of kind Type, we fallback to implementing prettyBy in terms of pretty like in the monomorphic case.

Note that in all those cases a Pretty instance for the data type has to already exist, so that we can derive a PrettyBy one in terms of it. If it doesn't exist or if your data type is not supported (for example, if it has three or more parameters of kind Type), then you'll need to provide the implementation manually.

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

prettyListBy is used to define the default PrettyBy instance for [a] and NonEmpty a. In normal circumstances only the prettyBy function is used. The default implementation of prettyListBy is in terms of defaultPrettyFunctorBy.

Instances

Instances details
PrettyBy PrettyConfigPlc DefaultFun Source # 
Instance details

Defined in PlutusCore.Default.Builtins

PrettyBy ConstConfig ByteString Source # 
Instance details

Defined in PlutusCore.Pretty.PrettyConst

PrettyBy ConstConfig Element Source # 
Instance details

Defined in PlutusCore.Crypto.BLS12_381.G1

Methods

prettyByConstConfigElementDoc ann Source #

prettyListByConstConfig → [Element] → Doc ann Source #

PrettyBy ConstConfig Element Source # 
Instance details

Defined in PlutusCore.Crypto.BLS12_381.G2

Methods

prettyByConstConfigElementDoc ann Source #

prettyListByConstConfig → [Element] → Doc ann Source #

PrettyBy ConstConfig MlResult Source # 
Instance details

Defined in PlutusCore.Crypto.BLS12_381.Pairing

PrettyBy ConstConfig Data Source # 
Instance details

Defined in PlutusCore.Pretty.PrettyConst

Methods

prettyByConstConfigDataDoc ann Source #

prettyListByConstConfig → [Data] → Doc ann Source #

PrettyDefaultBy config VoidPrettyBy config Void
>>> prettyBy () ([] :: [Void])
[]
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyBy ∷ config → VoidDoc ann Source #

prettyListBy ∷ config → [Void] → Doc ann Source #

PrettyDefaultBy config Int16PrettyBy config Int16 
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyBy ∷ config → Int16Doc ann Source #

prettyListBy ∷ config → [Int16] → Doc ann Source #

PrettyDefaultBy config Int32PrettyBy config Int32 
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyBy ∷ config → Int32Doc ann Source #

prettyListBy ∷ config → [Int32] → Doc ann Source #

PrettyDefaultBy config Int64PrettyBy config Int64 
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyBy ∷ config → Int64Doc ann Source #

prettyListBy ∷ config → [Int64] → Doc ann Source #

PrettyDefaultBy config Int8PrettyBy config Int8 
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyBy ∷ config → Int8Doc ann Source #

prettyListBy ∷ config → [Int8] → Doc ann Source #

PrettyDefaultBy config Word16PrettyBy config Word16 
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyBy ∷ config → Word16Doc ann Source #

prettyListBy ∷ config → [Word16] → Doc ann Source #

PrettyDefaultBy config Word32PrettyBy config Word32 
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyBy ∷ config → Word32Doc ann Source #

prettyListBy ∷ config → [Word32] → Doc ann Source #

PrettyDefaultBy config Word64PrettyBy config Word64 
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyBy ∷ config → Word64Doc ann Source #

prettyListBy ∷ config → [Word64] → Doc ann Source #

PrettyDefaultBy config Word8PrettyBy config Word8 
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyBy ∷ config → Word8Doc ann Source #

prettyListBy ∷ config → [Word8] → Doc ann Source #

HasPrettyConfigName config ⇒ PrettyBy config DeBruijn Source # 
Instance details

Defined in PlutusCore.DeBruijn.Internal

Methods

prettyBy ∷ config → DeBruijnDoc ann Source #

prettyListBy ∷ config → [DeBruijn] → Doc ann Source #

HasPrettyConfigName config ⇒ PrettyBy config FakeNamedDeBruijn Source # 
Instance details

Defined in PlutusCore.DeBruijn.Internal

Methods

prettyBy ∷ config → FakeNamedDeBruijnDoc ann Source #

prettyListBy ∷ config → [FakeNamedDeBruijn] → Doc ann Source #

HasPrettyConfigName config ⇒ PrettyBy config NamedDeBruijn Source # 
Instance details

Defined in PlutusCore.DeBruijn.Internal

Methods

prettyBy ∷ config → NamedDeBruijnDoc ann Source #

prettyListBy ∷ config → [NamedDeBruijn] → Doc ann Source #

HasPrettyConfigName config ⇒ PrettyBy config NamedTyDeBruijn Source # 
Instance details

Defined in PlutusCore.DeBruijn.Internal

Methods

prettyBy ∷ config → NamedTyDeBruijnDoc ann Source #

prettyListBy ∷ config → [NamedTyDeBruijn] → Doc ann Source #

HasPrettyConfigName config ⇒ PrettyBy config TyDeBruijn Source # 
Instance details

Defined in PlutusCore.DeBruijn.Internal

Methods

prettyBy ∷ config → TyDeBruijnDoc ann Source #

prettyListBy ∷ config → [TyDeBruijn] → Doc ann Source #

PrettyBy config ExBudget Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

Methods

prettyBy ∷ config → ExBudgetDoc ann Source #

prettyListBy ∷ config → [ExBudget] → Doc ann Source #

PrettyBy config ExRestrictingBudget Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

Methods

prettyBy ∷ config → ExRestrictingBudgetDoc ann Source #

prettyListBy ∷ config → [ExRestrictingBudget] → Doc ann Source #

PrettyBy config ExCPU Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Methods

prettyBy ∷ config → ExCPUDoc ann Source #

prettyListBy ∷ config → [ExCPU] → Doc ann Source #

PrettyBy config ExMemory Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Methods

prettyBy ∷ config → ExMemoryDoc ann Source #

prettyListBy ∷ config → [ExMemory] → Doc ann Source #

HasPrettyConfigName config ⇒ PrettyBy config Name Source # 
Instance details

Defined in PlutusCore.Name.Unique

Methods

prettyBy ∷ config → NameDoc ann Source #

prettyListBy ∷ config → [Name] → Doc ann Source #

HasPrettyConfigName config ⇒ PrettyBy config TyName Source # 
Instance details

Defined in PlutusCore.Name.Unique

Methods

prettyBy ∷ config → TyNameDoc ann Source #

prettyListBy ∷ config → [TyName] → Doc ann Source #

PrettyBy config CountingSt Source # 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

Methods

prettyBy ∷ config → CountingStDoc ann Source #

prettyListBy ∷ config → [CountingSt] → Doc ann Source #

PrettyBy config RestrictingSt Source # 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

Methods

prettyBy ∷ config → RestrictingStDoc ann Source #

prettyListBy ∷ config → [RestrictingSt] → Doc ann Source #

PrettyDefaultBy config TextPrettyBy config Text

Automatically converts all newlines to line.

>>> prettyBy () ("hello\nworld" :: Strict.Text)
hello
world
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyBy ∷ config → TextDoc ann Source #

prettyListBy ∷ config → [Text] → Doc ann Source #

PrettyDefaultBy config TextPrettyBy config Text

An instance for lazy Text. Identitical to the strict one.

Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyBy ∷ config → TextDoc ann Source #

prettyListBy ∷ config → [Text] → Doc ann Source #

PrettyDefaultBy config IntegerPrettyBy config Integer
>>> prettyBy () (2^(123 :: Int) :: Integer)
10633823966279326983230456482242756608
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyBy ∷ config → IntegerDoc ann Source #

prettyListBy ∷ config → [Integer] → Doc ann Source #

PrettyDefaultBy config NaturalPrettyBy config Natural
>>> prettyBy () (123 :: Natural)
123
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyBy ∷ config → NaturalDoc ann Source #

prettyListBy ∷ config → [Natural] → Doc ann Source #

PrettyDefaultBy config () ⇒ PrettyBy config ()
>>> prettyBy () ()
()

The argument is not used:

>>> prettyBy () (error "Strict?" :: ())
()
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyBy ∷ config → () → Doc ann Source #

prettyListBy ∷ config → [()] → Doc ann Source #

PrettyDefaultBy config BoolPrettyBy config Bool
>>> prettyBy () True
True
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyBy ∷ config → BoolDoc ann Source #

prettyListBy ∷ config → [Bool] → Doc ann Source #

PrettyDefaultBy config CharPrettyBy config Char

By default a String (i.e. [Char]) is converted to a Text first and then pretty-printed. So make sure that if you have any non-default pretty-printing for Char or Text, they're in sync.

>>> prettyBy () 'a'
a
>>> prettyBy () "abc"
abc
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyBy ∷ config → CharDoc ann Source #

prettyListBy ∷ config → [Char] → Doc ann Source #

PrettyDefaultBy config DoublePrettyBy config Double
>>> prettyBy () (pi :: Double)
3.141592653589793
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyBy ∷ config → DoubleDoc ann Source #

prettyListBy ∷ config → [Double] → Doc ann Source #

PrettyDefaultBy config FloatPrettyBy config Float
>>> prettyBy () (pi :: Float)
3.1415927
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyBy ∷ config → FloatDoc ann Source #

prettyListBy ∷ config → [Float] → Doc ann Source #

PrettyDefaultBy config IntPrettyBy config Int
>>> prettyBy () (123 :: Int)
123
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyBy ∷ config → IntDoc ann Source #

prettyListBy ∷ config → [Int] → Doc ann Source #

PrettyDefaultBy config WordPrettyBy config Word 
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyBy ∷ config → WordDoc ann Source #

prettyListBy ∷ config → [Word] → Doc ann Source #

DefaultPrettyPlcStrategy (Kind ann) ⇒ PrettyBy PrettyConfigPlc (Kind ann) Source # 
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Plc

Methods

prettyByPrettyConfigPlcKind ann → Doc ann0 Source #

prettyListByPrettyConfigPlc → [Kind ann] → Doc ann0 Source #

PrettyBy PrettyConfigPlc a ⇒ PrettyBy PrettyConfigPlc (ExpectedShapeOr a) Source # 
Instance details

Defined in PlutusCore.Error

DefaultPrettyPlcStrategy a ⇒ PrettyBy PrettyConfigPlc (PrettyAny a) Source # 
Instance details

Defined in PlutusCore.Pretty.Plc

DefaultPrettyPlcStrategy a ⇒ PrettyBy PrettyConfigPlcStrategy (PrettyAny a) Source # 
Instance details

Defined in PlutusCore.Pretty.Plc

PrettyConst a ⇒ PrettyBy ConstConfig (NoParens a) Source # 
Instance details

Defined in PlutusCore.Pretty.PrettyConst

Methods

prettyByConstConfigNoParens a → Doc ann Source #

prettyListByConstConfig → [NoParens a] → Doc ann Source #

DefaultPrettyBy ConstConfig (PrettyAny a) ⇒ PrettyBy ConstConfig (PrettyAny a) Source # 
Instance details

Defined in PlutusCore.Pretty.PrettyConst

Methods

prettyByConstConfigPrettyAny a → Doc ann Source #

prettyListByConstConfig → [PrettyAny a] → Doc ann Source #

PrettyBy RenderContext (DefaultUni a) Source # 
Instance details

Defined in PlutusCore.Default.Universe

PrettyBy RenderContext (SomeTypeIn DefaultUni) Source # 
Instance details

Defined in PlutusCore.Default.Universe

PrettyDefaultBy config (Identity a) ⇒ PrettyBy config (Identity a)
>>> prettyBy () (Identity True)
True
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyBy ∷ config → Identity a → Doc ann Source #

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

PrettyDefaultBy config (NonEmpty a) ⇒ PrettyBy config (NonEmpty a)

prettyBy for NonEmpty a is defined in terms of prettyListBy by default.

>>> prettyBy () (True :| [False])
[True, False]
>>> prettyBy () ('a' :| "bc")
abc
>>> prettyBy () (Just False :| [Nothing, Just True])
[False, True]
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyBy ∷ config → NonEmpty a → Doc ann Source #

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

PrettyDefaultBy config (Set a) ⇒ PrettyBy config (Set a) Source # 
Instance details

Defined in PlutusCore.Pretty.Extra

Methods

prettyBy ∷ config → Set a → Doc ann Source #

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

PrettyBy config (t NameAnn) ⇒ PrettyBy config (ScopeCheckError t) Source # 
Instance details

Defined in PlutusCore.Check.Scoping

Methods

prettyBy ∷ config → ScopeCheckError t → Doc ann Source #

prettyListBy ∷ config → [ScopeCheckError t] → Doc ann Source #

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

Defined in PlutusCore.Core.Type

Methods

prettyBy ∷ config → Normalized a → Doc ann Source #

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

(HasPrettyDefaults config ~ 'True, Pretty fun) ⇒ PrettyBy config (MachineError fun) Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

Methods

prettyBy ∷ config → MachineError fun → Doc ann Source #

prettyListBy ∷ config → [MachineError fun] → Doc ann Source #

PrettyBy config a ⇒ PrettyBy config (EvaluationResult a) Source # 
Instance details

Defined in PlutusCore.Evaluation.Result

Methods

prettyBy ∷ config → EvaluationResult a → Doc ann Source #

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

PrettyDefaultBy config (AsReadable a) ⇒ PrettyBy config (AsReadable a) Source # 
Instance details

Defined in PlutusCore.Pretty.Readable

Methods

prettyBy ∷ config → AsReadable a → Doc ann Source #

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

(Show fun, Ord fun) ⇒ PrettyBy config (CekExTally fun) Source # 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

Methods

prettyBy ∷ config → CekExTally fun → Doc ann Source #

prettyListBy ∷ config → [CekExTally fun] → Doc ann Source #

(Show fun, Ord fun) ⇒ PrettyBy config (TallyingSt fun) Source # 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

Methods

prettyBy ∷ config → TallyingSt fun → Doc ann Source #

prettyListBy ∷ config → [TallyingSt fun] → Doc ann Source #

Pretty a ⇒ PrettyBy config (IgnorePrettyConfig a)
>>> data Cfg = Cfg
>>> data D = D
>>> instance Pretty D where pretty D = "D"
>>> prettyBy Cfg $ IgnorePrettyConfig D
D
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyBy ∷ config → IgnorePrettyConfig a → Doc ann Source #

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

PrettyDefaultBy config a ⇒ PrettyBy config (PrettyCommon a) 
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyBy ∷ config → PrettyCommon a → Doc ann Source #

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

PrettyDefaultBy config (Maybe a) ⇒ PrettyBy config (Maybe a)

By default a [Maybe a] is converted to [a] first and only then pretty-printed.

>>> braces $ prettyBy () (Just True)
{True}
>>> braces $ prettyBy () (Nothing :: Maybe Bool)
{}
>>> prettyBy () [Just False, Nothing, Just True]
[False, True]
>>> prettyBy () [Nothing, Just 'a', Just 'b', Nothing, Just 'c']
abc
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyBy ∷ config → Maybe a → Doc ann Source #

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

PrettyDefaultBy config [a] ⇒ PrettyBy config [a]

prettyBy for [a] is defined in terms of prettyListBy by default.

>>> prettyBy () [True, False]
[True, False]
>>> prettyBy () "abc"
abc
>>> prettyBy () [Just False, Nothing, Just True]
[False, True]
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyBy ∷ config → [a] → Doc ann Source #

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

(PrettyUni uni, Pretty fun) ⇒ PrettyBy PrettyConfigPlc (CkValue uni fun) Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.Ck

Methods

prettyByPrettyConfigPlcCkValue uni fun → Doc ann Source #

prettyListByPrettyConfigPlc → [CkValue uni fun] → Doc ann Source #

(Closed uni, Everywhere uni PrettyConst) ⇒ PrettyBy ConstConfig (ValueOf uni a) Source # 
Instance details

Defined in PlutusCore.Pretty.PrettyConst

Methods

prettyByConstConfigValueOf uni a → Doc ann Source #

prettyListByConstConfig → [ValueOf uni a] → Doc ann Source #

(Closed uni, Everywhere uni PrettyConst) ⇒ PrettyBy ConstConfig (Some (ValueOf uni)) Source # 
Instance details

Defined in PlutusCore.Pretty.PrettyConst

Methods

prettyByConstConfigSome (ValueOf uni) → Doc ann Source #

prettyListByConstConfig → [Some (ValueOf uni)] → Doc ann Source #

PrettyDefaultBy config (Either a b) ⇒ PrettyBy config (Either a b) Source #

An instance extending the set of types supporting default pretty-printing with Either.

Instance details

Defined in PlutusPrelude

Methods

prettyBy ∷ config → Either a b → Doc ann Source #

prettyListBy ∷ config → [Either a b] → Doc ann Source #

PrettyDefaultBy config (Map k v) ⇒ PrettyBy config (Map k v) Source # 
Instance details

Defined in PlutusCore.Pretty.Extra

Methods

prettyBy ∷ config → Map k v → Doc ann Source #

prettyListBy ∷ config → [Map k v] → Doc ann Source #

(HasPrettyDefaults config ~ 'True, PrettyBy config structural, Pretty operational) ⇒ PrettyBy config (EvaluationError structural operational) Source # 
Instance details

Defined in PlutusCore.Evaluation.Error

Methods

prettyBy ∷ config → EvaluationError structural operational → Doc ann Source #

prettyListBy ∷ config → [EvaluationError structural operational] → Doc ann Source #

(PrettyBy config cause, PrettyBy config err) ⇒ PrettyBy config (ErrorWithCause err cause) Source # 
Instance details

Defined in PlutusCore.Evaluation.ErrorWithCause

Methods

prettyBy ∷ config → ErrorWithCause err cause → Doc ann Source #

prettyListBy ∷ config → [ErrorWithCause err cause] → Doc ann Source #

PrettyDefaultBy config (a, b) ⇒ PrettyBy config (a, b)
>>> prettyBy () (False, "abc")
(False, abc)
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyBy ∷ config → (a, b) → Doc ann Source #

prettyListBy ∷ config → [(a, b)] → Doc ann Source #

DefaultPrettyPlcStrategy (Type tyname uni ann) ⇒ PrettyBy PrettyConfigPlc (Type tyname uni ann) Source # 
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Plc

Methods

prettyByPrettyConfigPlcType tyname uni ann → Doc ann0 Source #

prettyListByPrettyConfigPlc → [Type tyname uni ann] → Doc ann0 Source #

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

Defined in PlutusCore.Error

Methods

prettyByPrettyConfigPlcError uni fun ann → Doc ann0 Source #

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

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

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Methods

prettyByPrettyConfigPlcCekValue uni fun ann → Doc ann0 Source #

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

PrettyDefaultBy config (Const a b) ⇒ PrettyBy config (Const a b)

Non-polykinded, because Pretty (Const a b) is not polykinded either.

>>> prettyBy () (Const 1 :: Const Integer Bool)
1
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyBy ∷ config → Const a b → Doc ann Source #

prettyListBy ∷ config → [Const a b] → Doc ann Source #

PrettyDefaultBy config (a, b, c) ⇒ PrettyBy config (a, b, c)
>>> prettyBy () ('a', "bcd", True)
(a, bcd, True)
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyBy ∷ config → (a, b, c) → Doc ann Source #

prettyListBy ∷ config → [(a, b, c)] → Doc ann Source #

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

Defined in PlutusCore.Error

Methods

prettyByPrettyConfigPlcTypeError term uni fun ann → Doc ann0 Source #

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

DefaultPrettyPlcStrategy (UnrestrictedProgram name uni fun ann) ⇒ PrettyBy PrettyConfigPlc (UnrestrictedProgram name uni fun ann) Source # 
Instance details

Defined in UntypedPlutusCore.Core.Instance.Flat

Methods

prettyByPrettyConfigPlcUnrestrictedProgram name uni fun ann → Doc ann0 Source #

prettyListByPrettyConfigPlc → [UnrestrictedProgram name uni fun ann] → Doc ann0 Source #

DefaultPrettyPlcStrategy (Program name uni fun ann) ⇒ PrettyBy PrettyConfigPlc (Program name uni fun ann) Source # 
Instance details

Defined in UntypedPlutusCore.Core.Instance.Pretty.Plc

Methods

prettyByPrettyConfigPlcProgram name uni fun ann → Doc ann0 Source #

prettyListByPrettyConfigPlc → [Program name uni fun ann] → Doc ann0 Source #

DefaultPrettyPlcStrategy (Term name uni fun ann) ⇒ PrettyBy PrettyConfigPlc (Term name uni fun ann) Source # 
Instance details

Defined in UntypedPlutusCore.Core.Instance.Pretty.Plc

Methods

prettyByPrettyConfigPlcTerm name uni fun ann → Doc ann0 Source #

prettyListByPrettyConfigPlc → [Term name uni fun ann] → Doc ann0 Source #

PrettyBy config (Term name uni fun a) ⇒ PrettyBy config (EvalOrder name uni fun a) Source # 
Instance details

Defined in UntypedPlutusCore.Purity

Methods

prettyBy ∷ config → EvalOrder name uni fun a → Doc ann Source #

prettyListBy ∷ config → [EvalOrder name uni fun a] → Doc ann Source #

PrettyBy config (Term name uni fun a) ⇒ PrettyBy config (EvalTerm name uni fun a) Source # 
Instance details

Defined in UntypedPlutusCore.Purity

Methods

prettyBy ∷ config → EvalTerm name uni fun a → Doc ann Source #

prettyListBy ∷ config → [EvalTerm name uni fun a] → Doc ann Source #

DefaultPrettyPlcStrategy (Program tyname name uni fun ann) ⇒ PrettyBy PrettyConfigPlc (Program tyname name uni fun ann) Source # 
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Plc

Methods

prettyByPrettyConfigPlcProgram tyname name uni fun ann → Doc ann0 Source #

prettyListByPrettyConfigPlc → [Program tyname name uni fun ann] → Doc ann0 Source #

DefaultPrettyPlcStrategy (Term tyname name uni fun ann) ⇒ PrettyBy PrettyConfigPlc (Term tyname name uni fun ann) Source # 
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Plc

Methods

prettyByPrettyConfigPlcTerm tyname name uni fun ann → Doc ann0 Source #

prettyListByPrettyConfigPlc → [Term tyname name uni fun ann] → Doc ann0 Source #

(Pretty ann, PrettyBy config (Type tyname uni ann), PrettyBy config (Term tyname name uni fun ann)) ⇒ PrettyBy config (NormCheckError tyname name uni fun ann) Source # 
Instance details

Defined in PlutusCore.Error

Methods

prettyBy ∷ config → NormCheckError tyname name uni fun ann → Doc ann0 Source #

prettyListBy ∷ config → [NormCheckError tyname name uni fun ann] → Doc ann0 Source #

Pretty ann ⇒ PrettyBy (PrettyConfigClassic configName) (Kind ann) Source # 
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Classic

Methods

prettyByPrettyConfigClassic configName → Kind ann → Doc ann0 Source #

prettyListByPrettyConfigClassic configName → [Kind ann] → Doc ann0 Source #

PrettyBy (PrettyConfigReadable configName) (Kind a) Source # 
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Readable

Methods

prettyByPrettyConfigReadable configName → Kind a → Doc ann Source #

prettyListByPrettyConfigReadable configName → [Kind a] → Doc ann Source #

PrettyReadableBy configName a ⇒ PrettyBy (PrettyConfigReadable configName) (Parened a) Source # 
Instance details

Defined in PlutusCore.Pretty.Readable

Methods

prettyByPrettyConfigReadable configName → Parened a → Doc ann Source #

prettyListByPrettyConfigReadable configName → [Parened a] → Doc ann Source #

PrettyReadableBy configName tyname ⇒ PrettyBy (PrettyConfigReadable configName) (TyVarDecl tyname ann) Source # 
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Readable

Methods

prettyByPrettyConfigReadable configName → TyVarDecl tyname ann → Doc ann0 Source #

prettyListByPrettyConfigReadable configName → [TyVarDecl tyname ann] → Doc ann0 Source #

(PrettyClassicBy configName tyname, PrettyParens (SomeTypeIn uni), Pretty ann) ⇒ PrettyBy (PrettyConfigClassic configName) (Type tyname uni ann) Source # 
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Classic

Methods

prettyByPrettyConfigClassic configName → Type tyname uni ann → Doc ann0 Source #

prettyListByPrettyConfigClassic configName → [Type tyname uni ann] → Doc ann0 Source #

(PrettyReadableBy configName tyname, PrettyParens (SomeTypeIn uni)) ⇒ PrettyBy (PrettyConfigReadable configName) (Type tyname uni a) Source # 
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Readable

Methods

prettyByPrettyConfigReadable configName → Type tyname uni a → Doc ann Source #

prettyListByPrettyConfigReadable configName → [Type tyname uni a] → Doc ann Source #

(PrettyClassic name, PrettyUni uni, Pretty fun, Pretty ann) ⇒ PrettyBy (PrettyConfigClassic PrettyConfigName) (UnrestrictedProgram name uni fun ann) Source # 
Instance details

Defined in UntypedPlutusCore.Core.Instance.Flat

(PrettyClassicBy configName (Term name uni fun ann), Pretty ann) ⇒ PrettyBy (PrettyConfigClassic configName) (Program name uni fun ann) Source # 
Instance details

Defined in UntypedPlutusCore.Core.Instance.Pretty.Classic

Methods

prettyByPrettyConfigClassic configName → Program name uni fun ann → Doc ann0 Source #

prettyListByPrettyConfigClassic configName → [Program name uni fun ann] → Doc ann0 Source #

(PrettyClassicBy configName name, PrettyUni uni, Pretty fun, Pretty ann) ⇒ PrettyBy (PrettyConfigClassic configName) (Term name uni fun ann) Source # 
Instance details

Defined in UntypedPlutusCore.Core.Instance.Pretty.Classic

Methods

prettyByPrettyConfigClassic configName → Term name uni fun ann → Doc ann0 Source #

prettyListByPrettyConfigClassic configName → [Term name uni fun ann] → Doc ann0 Source #

(PrettyReadable name, PrettyUni uni, Pretty fun) ⇒ PrettyBy (PrettyConfigReadable PrettyConfigName) (UnrestrictedProgram name uni fun ann) Source # 
Instance details

Defined in UntypedPlutusCore.Core.Instance.Flat

(PrettyReadableBy configName tyname, PrettyReadableBy configName name, PrettyUni uni) ⇒ PrettyBy (PrettyConfigReadable configName) (VarDecl tyname name uni ann) Source # 
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Readable

Methods

prettyByPrettyConfigReadable configName → VarDecl tyname name uni ann → Doc ann0 Source #

prettyListByPrettyConfigReadable configName → [VarDecl tyname name uni ann] → Doc ann0 Source #

PrettyReadableBy configName (Term name uni fun a) ⇒ PrettyBy (PrettyConfigReadable configName) (Program name uni fun a) Source # 
Instance details

Defined in UntypedPlutusCore.Core.Instance.Pretty.Readable

Methods

prettyByPrettyConfigReadable configName → Program name uni fun a → Doc ann Source #

prettyListByPrettyConfigReadable configName → [Program name uni fun a] → Doc ann Source #

(PrettyReadableBy configName name, PrettyUni uni, Pretty fun, Show configName) ⇒ PrettyBy (PrettyConfigReadable configName) (Term name uni fun a) Source # 
Instance details

Defined in UntypedPlutusCore.Core.Instance.Pretty.Readable

Methods

prettyByPrettyConfigReadable configName → Term name uni fun a → Doc ann Source #

prettyListByPrettyConfigReadable configName → [Term name uni fun a] → Doc ann Source #

(PrettyClassicBy configName (Term tyname name uni fun ann), Pretty ann) ⇒ PrettyBy (PrettyConfigClassic configName) (Program tyname name uni fun ann) Source # 
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Classic

Methods

prettyByPrettyConfigClassic configName → Program tyname name uni fun ann → Doc ann0 Source #

prettyListByPrettyConfigClassic configName → [Program tyname name uni fun ann] → Doc ann0 Source #

(PrettyClassicBy configName tyname, PrettyClassicBy configName name, PrettyUni uni, Pretty fun, Pretty ann) ⇒ PrettyBy (PrettyConfigClassic configName) (Term tyname name uni fun ann) Source # 
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Classic

Methods

prettyByPrettyConfigClassic configName → Term tyname name uni fun ann → Doc ann0 Source #

prettyListByPrettyConfigClassic configName → [Term tyname name uni fun ann] → Doc ann0 Source #

PrettyReadableBy configName (Term tyname name uni fun a) ⇒ PrettyBy (PrettyConfigReadable configName) (Program tyname name uni fun a) Source # 
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Readable

Methods

prettyByPrettyConfigReadable configName → Program tyname name uni fun a → Doc ann Source #

prettyListByPrettyConfigReadable configName → [Program tyname name uni fun a] → Doc ann Source #

(PrettyReadableBy configName tyname, PrettyReadableBy configName name, PrettyUni uni, Pretty fun) ⇒ PrettyBy (PrettyConfigReadable configName) (Term tyname name uni fun a) Source # 
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Readable

Methods

prettyByPrettyConfigReadable configName → Term tyname name uni fun a → Doc ann Source #

prettyListByPrettyConfigReadable configName → [Term tyname name uni fun a] → Doc ann Source #

type family HasPrettyDefaults config ∷ Bool Source #

Determines whether a pretty-printing config allows default pretty-printing for types that support it. I.e. it's possible to create a new config and get access to pretty-printing for all types supporting default pretty-printing just by providing the right type instance. Example:

>>> data DefCfg = DefCfg
>>> type instance HasPrettyDefaults DefCfg = 'True
>>> prettyBy DefCfg (['a', 'b', 'c'], (1 :: Int), Just True)
(abc, 1, True)

The set of types supporting default pretty-printing is determined by the prettyprinter library: whatever there has a Pretty instance also supports default pretty-printing in this library and the behavior of pretty x and prettyBy config_with_defaults x must be identical when x is one of such types.

It is possible to override default pretty-printing. For this you need to specify that HasPrettyDefaults is 'False for your config and then define a NonDefaultPrettyBy config instance for each of the types supporting default pretty-printing that you want to pretty-print values of. Note that once HasPrettyDefaults is specified to be 'False, all defaults are lost for your config, so you can't override default pretty-printing for one type and keep the defaults for all the others. I.e. if you have

>>> data NonDefCfg = NonDefCfg
>>> type instance HasPrettyDefaults NonDefCfg = 'False

then you have no defaults available and an attempt to pretty-print a value of a type supporting default pretty-printing

prettyBy NonDefCfg True

results in a type error:

• No instance for (NonDefaultPrettyBy NonDef Bool)
     arising from a use of ‘prettyBy’

As the error suggests you need to provide a NonDefaultPrettyBy instance explicitly:

>>> instance NonDefaultPrettyBy NonDefCfg Bool where nonDefaultPrettyBy _ b = if b then "t" else "f"
>>> prettyBy NonDefCfg True
t

It is also possible not to provide any implementation for nonDefaultPrettyBy, in which case it defaults to being the default pretty-printing for the given type. This can be useful to recover default pretty-printing for types pretty-printing of which you don't want to override:

>>> instance NonDefaultPrettyBy NonDefCfg Int
>>> prettyBy NonDefCfg (42 :: Int)
42

Look into test/NonDefault.hs for an extended example.

We could give the user more fine-grained control over what defaults to override instead of requiring to explicitly provide all the instances whenever there's a need to override any default behavior, but that would complicate the library even more, so we opted for not doing that at the moment.

Note that you can always override default behavior by wrapping a type in newtype and providing a PrettyBy config_name instance for that newtype.

Also note that if you want to extend the set of types supporting default pretty-printing it's not enough to provide a Pretty instance for your type (such logic is hardly expressible in present day Haskell). Read the docs of DefaultPrettyBy for how to extend the set of types supporting default pretty-printing.

Instances

Instances details
type HasPrettyDefaults PrettyConfigName Source # 
Instance details

Defined in PlutusCore.Pretty.ConfigName

type HasPrettyDefaults PrettyConfigPlc Source # 
Instance details

Defined in PlutusCore.Pretty.Plc

type HasPrettyDefaults ConstConfig Source # 
Instance details

Defined in PlutusCore.Pretty.PrettyConst

type HasPrettyDefaults ()

prettyBy () works like pretty for types supporting default pretty-printing.

Instance details

Defined in Text.PrettyBy.Internal

type HasPrettyDefaults (PrettyConfigClassic _1) Source # 
Instance details

Defined in PlutusCore.Pretty.Classic

type HasPrettyDefaults (PrettyConfigReadable _1) Source # 
Instance details

Defined in PlutusCore.Pretty.Readable

type HasPrettyDefaults (Sole config) Source # 
Instance details

Defined in PlutusCore.Pretty.Extra

type PrettyDefaultBy config = DispatchPrettyDefaultBy (NonStuckHasPrettyDefaults config) config Source #

PrettyDefaultBy config a is the same thing as PrettyBy config a, when a supports default pretty-printing. Thus PrettyDefaultBy config a and PrettyBy config a are interchangeable constraints for such types, but the latter throws an annoying "this makes type inference for inner bindings fragile" warning, unlike the former. PrettyDefaultBy config a reads as "a supports default pretty-printing and can be pretty-printed via config in either default or non-default manner depending on whether config supports default pretty-printing".

newtype PrettyAny a Source #

A newtype wrapper around a provided for the purporse of defining PrettyBy instances handling any a. For example you can wrap values with the PrettyAny constructor directly like in this last line of

>>> data ViaShow = ViaShow
>>> instance Show a => PrettyBy ViaShow (PrettyAny a) where prettyBy ViaShow = pretty . show . unPrettyAny
>>> prettyBy ViaShow $ PrettyAny True
True

or you can use the type to via-derive instances:

>>> data D = D deriving stock (Show)
>>> deriving via PrettyAny D instance PrettyBy ViaShow D
>>> prettyBy ViaShow D
D

One important use case is handling sum-type configs. For example having two configs you can define their sum and derive PrettyBy for the unified config in terms of its components:

>>> data UpperCase = UpperCase
>>> data LowerCase = LowerCase
>>> data Case = CaseUpperCase UpperCase | CaseLowerCase LowerCase
>>> instance (PrettyBy UpperCase a, PrettyBy LowerCase a) => PrettyBy Case (PrettyAny a) where prettyBy (CaseUpperCase upper) = prettyBy upper . unPrettyAny; prettyBy (CaseLowerCase lower) = prettyBy lower . unPrettyAny

Then having a data type implementing both PrettyBy UpperCase and PrettyBy LowerCase you can derive PrettyBy Case for that data type:

>>> data D = D
>>> instance PrettyBy UpperCase D where prettyBy UpperCase D = "D"
>>> instance PrettyBy LowerCase D where prettyBy LowerCase D = "d"
>>> deriving via PrettyAny D instance PrettyBy Case D
>>> prettyBy UpperCase D
D
>>> prettyBy LowerCase D
d

Look into test/Universal.hs for an extended example.

Constructors

PrettyAny 

Fields

class Render str where Source #

A class for rendering Docs as string types.

Methods

renderDoc ann → str Source #

Render a Doc as a string type.

Instances

Instances details
Render Text 
Instance details

Defined in Text.PrettyBy.Default

Methods

renderDoc ann → Text Source #

Render Text 
Instance details

Defined in Text.PrettyBy.Default

Methods

renderDoc ann → Text Source #

a ~ CharRender [a] 
Instance details

Defined in Text.PrettyBy.Default

Methods

renderDoc ann → [a] Source #

display ∷ ∀ str a. (Pretty a, Render str) ⇒ a → str Source #

Pretty-print and render a value as a string type.

GHCi

printPrettyPretty a ⇒ a → IO () Source #

A command suitable for use in GHCi as an interactive printer.

Text

showTextShow a ⇒ a → Text Source #

class Default a where Source #

A class for types with a default value.

Minimal complete definition

Nothing

Methods

def ∷ a Source #

The default value for this type.

Instances

Instances details
Default All 
Instance details

Defined in Data.Default.Class

Methods

defAll Source #

Default Any 
Instance details

Defined in Data.Default.Class

Methods

defAny Source #

Default CClock 
Instance details

Defined in Data.Default.Class

Methods

defCClock Source #

Default CDouble 
Instance details

Defined in Data.Default.Class

Methods

defCDouble Source #

Default CFloat 
Instance details

Defined in Data.Default.Class

Methods

defCFloat Source #

Default CInt 
Instance details

Defined in Data.Default.Class

Methods

defCInt Source #

Default CIntMax 
Instance details

Defined in Data.Default.Class

Methods

defCIntMax Source #

Default CIntPtr 
Instance details

Defined in Data.Default.Class

Methods

defCIntPtr Source #

Default CLLong 
Instance details

Defined in Data.Default.Class

Methods

defCLLong Source #

Default CLong 
Instance details

Defined in Data.Default.Class

Methods

defCLong Source #

Default CPtrdiff 
Instance details

Defined in Data.Default.Class

Methods

defCPtrdiff Source #

Default CSUSeconds 
Instance details

Defined in Data.Default.Class

Methods

defCSUSeconds Source #

Default CShort 
Instance details

Defined in Data.Default.Class

Methods

defCShort Source #

Default CSigAtomic 
Instance details

Defined in Data.Default.Class

Methods

defCSigAtomic Source #

Default CSize 
Instance details

Defined in Data.Default.Class

Methods

defCSize Source #

Default CTime 
Instance details

Defined in Data.Default.Class

Methods

defCTime Source #

Default CUInt 
Instance details

Defined in Data.Default.Class

Methods

defCUInt Source #

Default CUIntMax 
Instance details

Defined in Data.Default.Class

Methods

defCUIntMax Source #

Default CUIntPtr 
Instance details

Defined in Data.Default.Class

Methods

defCUIntPtr Source #

Default CULLong 
Instance details

Defined in Data.Default.Class

Methods

defCULLong Source #

Default CULong 
Instance details

Defined in Data.Default.Class

Methods

defCULong Source #

Default CUSeconds 
Instance details

Defined in Data.Default.Class

Methods

defCUSeconds Source #

Default CUShort 
Instance details

Defined in Data.Default.Class

Methods

defCUShort Source #

Default Int16 
Instance details

Defined in Data.Default.Class

Methods

defInt16 Source #

Default Int32 
Instance details

Defined in Data.Default.Class

Methods

defInt32 Source #

Default Int64 
Instance details

Defined in Data.Default.Class

Methods

defInt64 Source #

Default Int8 
Instance details

Defined in Data.Default.Class

Methods

defInt8 Source #

Default Word16 
Instance details

Defined in Data.Default.Class

Methods

defWord16 Source #

Default Word32 
Instance details

Defined in Data.Default.Class

Methods

defWord32 Source #

Default Word64 
Instance details

Defined in Data.Default.Class

Methods

defWord64 Source #

Default Word8 
Instance details

Defined in Data.Default.Class

Methods

defWord8 Source #

Default Ordering 
Instance details

Defined in Data.Default.Class

Methods

defOrdering Source #

Default ModelFiveArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Default ModelFourArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Default ModelOneArgument Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Default ModelSixArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Default ModelThreeArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Default ModelTwoArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Default ShowKinds Source # 
Instance details

Defined in PlutusCore.Pretty.Readable

Methods

defShowKinds Source #

Default Integer 
Instance details

Defined in Data.Default.Class

Methods

defInteger Source #

Default () 
Instance details

Defined in Data.Default.Class

Methods

def ∷ () Source #

Default Double 
Instance details

Defined in Data.Default.Class

Methods

defDouble Source #

Default Float 
Instance details

Defined in Data.Default.Class

Methods

defFloat Source #

Default Int 
Instance details

Defined in Data.Default.Class

Methods

defInt Source #

Default Word 
Instance details

Defined in Data.Default.Class

Methods

defWord Source #

(Default a, RealFloat a) ⇒ Default (Complex a) 
Instance details

Defined in Data.Default.Class

Methods

defComplex a Source #

Default (First a) 
Instance details

Defined in Data.Default.Class

Methods

defFirst a Source #

Default (Last a) 
Instance details

Defined in Data.Default.Class

Methods

defLast a Source #

Default a ⇒ Default (Dual a) 
Instance details

Defined in Data.Default.Class

Methods

defDual a Source #

Default (Endo a) 
Instance details

Defined in Data.Default.Class

Methods

defEndo a Source #

Num a ⇒ Default (Product a) 
Instance details

Defined in Data.Default.Class

Methods

defProduct a Source #

Num a ⇒ Default (Sum a) 
Instance details

Defined in Data.Default.Class

Methods

defSum a Source #

Integral a ⇒ Default (Ratio a) 
Instance details

Defined in Data.Default.Class

Methods

defRatio a Source #

Default a ⇒ Default (IO a) 
Instance details

Defined in Data.Default.Class

Methods

defIO a Source #

(Default (BuiltinSemanticsVariant fun1), Default (BuiltinSemanticsVariant fun2)) ⇒ Default (BuiltinSemanticsVariant (Either fun1 fun2)) Source # 
Instance details

Defined in PlutusCore.Examples.Builtins

Methods

defBuiltinSemanticsVariant (Either fun1 fun2) Source #

Default (BuiltinSemanticsVariant DefaultFun) Source # 
Instance details

Defined in PlutusCore.Default.Builtins

Default (BuiltinSemanticsVariant ExtensionFun) Source # 
Instance details

Defined in PlutusCore.Examples.Builtins

AllArgumentModels Default f ⇒ Default (BuiltinCostModelBase f) Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

Default model ⇒ Default (CostingFun model) Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

defCostingFun model Source #

Default (Maybe a) 
Instance details

Defined in Data.Default.Class

Methods

defMaybe a Source #

Default [a] 
Instance details

Defined in Data.Default.Class

Methods

def ∷ [a] Source #

(Default a, Default b) ⇒ Default (a, b) 
Instance details

Defined in Data.Default.Class

Methods

def ∷ (a, b) Source #

Default r ⇒ Default (e → r) 
Instance details

Defined in Data.Default.Class

Methods

def ∷ e → r Source #

(Default a, Default b, Default c) ⇒ Default (a, b, c) 
Instance details

Defined in Data.Default.Class

Methods

def ∷ (a, b, c) Source #

(Default a, Default b, Default c, Default d) ⇒ Default (a, b, c, d) 
Instance details

Defined in Data.Default.Class

Methods

def ∷ (a, b, c, d) Source #

(Default a, Default b, Default c, Default d, Default e) ⇒ Default (a, b, c, d, e) 
Instance details

Defined in Data.Default.Class

Methods

def ∷ (a, b, c, d, e) Source #

(Default a, Default b, Default c, Default d, Default e, Default f) ⇒ Default (a, b, c, d, e, f) 
Instance details

Defined in Data.Default.Class

Methods

def ∷ (a, b, c, d, e, f) Source #

(Default a, Default b, Default c, Default d, Default e, Default f, Default g) ⇒ Default (a, b, c, d, e, f, g) 
Instance details

Defined in Data.Default.Class

Methods

def ∷ (a, b, c, d, e, f, g) Source #

Lists

zipExact ∷ [a] → [b] → Maybe [(a, b)] Source #

Zips two lists of the same length together, returning Nothing if they are not the same length.

allSameEq a ⇒ [a] → Bool Source #

distinctEq a ⇒ [a] → Bool Source #

unsafeFromRightShow e ⇒ Either e a → a Source #

Similar to Maybe's fromJust. Returns the Right and errors out with the show instance of the Left.

tryErrorMonadError e m ⇒ m a → m (Either e a) Source #

A MonadError version of try.

TODO: remove when we switch to mtl>=2.3

Orphan instances

(PrettyBy config a, PrettyBy config b) ⇒ DefaultPrettyBy config (Either a b) Source #

Default pretty-printing for the spine of Either (elements are pretty-printed the way PrettyBy config constraints specify it).

Instance details

Methods

defaultPrettyBy ∷ config → Either a b → Doc ann Source #

defaultPrettyListBy ∷ config → [Either a b] → Doc ann Source #

PrettyDefaultBy config (Either a b) ⇒ PrettyBy config (Either a b) Source #

An instance extending the set of types supporting default pretty-printing with Either.

Instance details

Methods

prettyBy ∷ config → Either a b → Doc ann Source #

prettyListBy ∷ config → [Either a b] → Doc ann Source #

(Pretty a, Pretty b) ⇒ Pretty (Either a b) Source # 
Instance details

Methods

prettyEither a b → Doc ann Source #

prettyList ∷ [Either a b] → Doc ann Source #