lorentz-0.11.0: EDSL for the Michelson Language
Safe HaskellNone
LanguageHaskell2010

Lorentz.Value

Description

Re-exports typed Value, CValue, some core types, some helpers and defines aliases for constructors of typed values.

Synopsis

Documentation

type Value = Value' Instr #

class WellTypedToT a => IsoValue a where #

Minimal complete definition

Nothing

Associated Types

type ToT a :: T #

type ToT a = GValueType (Rep a)

Methods

toVal :: a -> Value (ToT a) #

fromVal :: Value (ToT a) -> a #

Instances

Instances details
IsoValue Bool 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Bool :: T #

Methods

toVal :: Bool -> Value (ToT Bool) #

fromVal :: Value (ToT Bool) -> Bool #

IsoValue Integer 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Integer :: T #

IsoValue Natural 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Natural :: T #

IsoValue () 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT () :: T #

Methods

toVal :: () -> Value (ToT ()) #

fromVal :: Value (ToT ()) -> () #

IsoValue ByteString 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT ByteString :: T #

(DoNotUseTextError :: Constraint) => IsoValue Text 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Text :: T #

Methods

toVal :: Text -> Value (ToT Text) #

fromVal :: Value (ToT Text) -> Text #

IsoValue Void 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Void :: T #

Methods

toVal :: Void -> Value (ToT Void) #

fromVal :: Value (ToT Void) -> Void #

IsoValue MText 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT MText :: T #

IsoValue Operation 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Operation :: T #

IsoValue EpAddress 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT EpAddress :: T #

IsoValue MyCompoundType 
Instance details

Defined in Michelson.Typed.Haskell.Instr.Sum

Associated Types

type ToT MyCompoundType :: T #

Methods

toVal :: MyCompoundType -> Value (ToT MyCompoundType) #

fromVal :: Value (ToT MyCompoundType) -> MyCompoundType #

IsoValue Address 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Address :: T #

IsoValue Bls12381Fr 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Bls12381Fr :: T #

IsoValue Bls12381G1 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Bls12381G1 :: T #

IsoValue Bls12381G2 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Bls12381G2 :: T #

IsoValue ChainId 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT ChainId :: T #

IsoValue KeyHash 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT KeyHash :: T #

IsoValue Mutez 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Mutez :: T #

IsoValue PublicKey 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT PublicKey :: T #

IsoValue Signature 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Signature :: T #

IsoValue Timestamp 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Timestamp :: T #

IsoValue MyType2 
Instance details

Defined in Michelson.Typed.Haskell.Instr.Product

Associated Types

type ToT MyType2 :: T #

Methods

toVal :: MyType2 -> Value (ToT MyType2) #

fromVal :: Value (ToT MyType2) -> MyType2 #

IsoValue MyType 
Instance details

Defined in Michelson.Typed.Haskell.Instr.Sum

Associated Types

type ToT MyType :: T #

Methods

toVal :: MyType -> Value (ToT MyType) #

fromVal :: Value (ToT MyType) -> MyType #

IsoValue MyType' 
Instance details

Defined in Michelson.Typed.Haskell.Instr.Sum

Associated Types

type ToT MyType' :: T #

Methods

toVal :: MyType' -> Value (ToT MyType') #

fromVal :: Value (ToT MyType') -> MyType' #

IsoValue MyEnum 
Instance details

Defined in Michelson.Typed.Haskell.Instr.Sum

Associated Types

type ToT MyEnum :: T #

Methods

toVal :: MyEnum -> Value (ToT MyEnum) #

fromVal :: Value (ToT MyEnum) -> MyEnum #

IsoValue MyTypeWithNamedField 
Instance details

Defined in Michelson.Typed.Haskell.Instr.Sum

Associated Types

type ToT MyTypeWithNamedField :: T #

Methods

toVal :: MyTypeWithNamedField -> Value (ToT MyTypeWithNamedField) #

fromVal :: Value (ToT MyTypeWithNamedField) -> MyTypeWithNamedField #

IsoValue Never Source # 
Instance details

Defined in Lorentz.Value

Associated Types

type ToT Never :: T #

IsoValue UnspecifiedError Source # 
Instance details

Defined in Lorentz.Errors

Associated Types

type ToT UnspecifiedError :: T #

IsoValue Empty Source # 
Instance details

Defined in Lorentz.Empty

Associated Types

type ToT Empty :: T #

IsoValue a => IsoValue [a] 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT [a] :: T #

Methods

toVal :: [a] -> Value (ToT [a]) #

fromVal :: Value (ToT [a]) -> [a] #

IsoValue a => IsoValue (Maybe a) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (Maybe a) :: T #

Methods

toVal :: Maybe a -> Value (ToT (Maybe a)) #

fromVal :: Value (ToT (Maybe a)) -> Maybe a #

IsoValue a => IsoValue (Identity a) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (Identity a) :: T #

Methods

toVal :: Identity a -> Value (ToT (Identity a)) #

fromVal :: Value (ToT (Identity a)) -> Identity a #

(Comparable (ToT c), Ord c, IsoValue c) => IsoValue (Set c) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (Set c) :: T #

Methods

toVal :: Set c -> Value (ToT (Set c)) #

fromVal :: Value (ToT (Set c)) -> Set c #

WellTyped t => IsoValue (Value t) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (Value t) :: T #

Methods

toVal :: Value t -> Value (ToT (Value t)) #

fromVal :: Value (ToT (Value t)) -> Value t #

WellTypedToT arg => IsoValue (ContractRef arg) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (ContractRef arg) :: T #

Methods

toVal :: ContractRef arg -> Value (ToT (ContractRef arg)) #

fromVal :: Value (ToT (ContractRef arg)) -> ContractRef arg #

WellTypedIsoValue r => IsoValue (ShouldHaveEntrypoints r) Source # 
Instance details

Defined in Lorentz.Entrypoints.Helpers

Associated Types

type ToT (ShouldHaveEntrypoints r) :: T #

IsoValue (FutureContract arg) Source # 
Instance details

Defined in Lorentz.Address

Associated Types

type ToT (FutureContract arg) :: T #

IsoValue (TSignature a) Source # 
Instance details

Defined in Lorentz.Bytes

Associated Types

type ToT (TSignature a) :: T #

IsoValue (Packed a) Source # 
Instance details

Defined in Lorentz.Bytes

Associated Types

type ToT (Packed a) :: T #

Methods

toVal :: Packed a -> Value (ToT (Packed a)) #

fromVal :: Value (ToT (Packed a)) -> Packed a #

(WellTypedIsoValue (CustomErrorRep tag), TypeError ('Text "CustomError has no IsoValue instance") :: Constraint) => IsoValue (CustomError tag) Source #

This instance cannot be implemented, use IsError instance instead.

Instance details

Defined in Lorentz.Errors

Associated Types

type ToT (CustomError tag) :: T #

Methods

toVal :: CustomError tag -> Value (ToT (CustomError tag)) #

fromVal :: Value (ToT (CustomError tag)) -> CustomError tag #

(WellTypedIsoValue (VoidResult r), TypeError ('Text "No IsoValue instance for VoidResult " :<>: 'ShowType r) :: Constraint) => IsoValue (VoidResult r) Source # 
Instance details

Defined in Lorentz.Macro

Associated Types

type ToT (VoidResult r) :: T #

IsoValue (UParam entries) Source # 
Instance details

Defined in Lorentz.UParam

Associated Types

type ToT (UParam entries) :: T #

Methods

toVal :: UParam entries -> Value (ToT (UParam entries)) #

fromVal :: Value (ToT (UParam entries)) -> UParam entries #

(IsoValue l, IsoValue r) => IsoValue (Either l r) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (Either l r) :: T #

Methods

toVal :: Either l r -> Value (ToT (Either l r)) #

fromVal :: Value (ToT (Either l r)) -> Either l r #

(IsoValue a, IsoValue b) => IsoValue (a, b) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (a, b) :: T #

Methods

toVal :: (a, b) -> Value (ToT (a, b)) #

fromVal :: Value (ToT (a, b)) -> (a, b) #

(Comparable (ToT k), Ord k, IsoValue k, IsoValue v) => IsoValue (Map k v) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (Map k v) :: T #

Methods

toVal :: Map k v -> Value (ToT (Map k v)) #

fromVal :: Value (ToT (Map k v)) -> Map k v #

(WellTypedToT k, WellTypedToT v, Comparable (ToT k), Ord k, IsoValue k, IsoValue v) => IsoValue (BigMap k v) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (BigMap k v) :: T #

Methods

toVal :: BigMap k v -> Value (ToT (BigMap k v)) #

fromVal :: Value (ToT (BigMap k v)) -> BigMap k v #

(WellTypedToT (ZippedStack inp), WellTypedToT (ZippedStack out), ZipInstr inp, ZipInstr out) => IsoValue (inp :-> out) Source # 
Instance details

Defined in Lorentz.Zip

Associated Types

type ToT (inp :-> out) :: T #

Methods

toVal :: (inp :-> out) -> Value (ToT (inp :-> out)) #

fromVal :: Value (ToT (inp :-> out)) -> inp :-> out #

IsoValue (TAddress p) Source # 
Instance details

Defined in Lorentz.Address

Associated Types

type ToT (TAddress p) :: T #

Methods

toVal :: TAddress p -> Value (ToT (TAddress p)) #

fromVal :: Value (ToT (TAddress p)) -> TAddress p #

IsoValue cp => IsoValue (ParameterWrapper deriv cp) Source # 
Instance details

Defined in Lorentz.Entrypoints.Manual

Associated Types

type ToT (ParameterWrapper deriv cp) :: T #

Methods

toVal :: ParameterWrapper deriv cp -> Value (ToT (ParameterWrapper deriv cp)) #

fromVal :: Value (ToT (ParameterWrapper deriv cp)) -> ParameterWrapper deriv cp #

IsoValue (Hash alg a) Source # 
Instance details

Defined in Lorentz.Bytes

Associated Types

type ToT (Hash alg a) :: T #

Methods

toVal :: Hash alg a -> Value (ToT (Hash alg a)) #

fromVal :: Value (ToT (Hash alg a)) -> Hash alg a #

IsoValue (Extensible x) Source # 
Instance details

Defined in Lorentz.Extensible

Associated Types

type ToT (Extensible x) :: T #

(WellTypedIsoValue r, WellTypedIsoValue a) => IsoValue (Void_ a r) Source # 
Instance details

Defined in Lorentz.Macro

Associated Types

type ToT (Void_ a r) :: T #

Methods

toVal :: Void_ a r -> Value (ToT (Void_ a r)) #

fromVal :: Value (ToT (Void_ a r)) -> Void_ a r #

(WellTypedIsoValue r, WellTypedIsoValue a) => IsoValue (View a r) Source # 
Instance details

Defined in Lorentz.Macro

Associated Types

type ToT (View a r) :: T #

Methods

toVal :: View a r -> Value (ToT (View a r)) #

fromVal :: Value (ToT (View a r)) -> View a r #

(IsoValue a, IsoValue b, IsoValue c) => IsoValue (a, b, c) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (a, b, c) :: T #

Methods

toVal :: (a, b, c) -> Value (ToT (a, b, c)) #

fromVal :: Value (ToT (a, b, c)) -> (a, b, c) #

IsoValue a => IsoValue (NamedF Maybe a name) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (NamedF Maybe a name) :: T #

Methods

toVal :: NamedF Maybe a name -> Value (ToT (NamedF Maybe a name)) #

fromVal :: Value (ToT (NamedF Maybe a name)) -> NamedF Maybe a name #

IsoValue a => IsoValue (NamedF Identity a name) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (NamedF Identity a name) :: T #

Methods

toVal :: NamedF Identity a name -> Value (ToT (NamedF Identity a name)) #

fromVal :: Value (ToT (NamedF Identity a name)) -> NamedF Identity a name #

(IsoValue a, IsoValue b, IsoValue c, IsoValue d) => IsoValue (a, b, c, d) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (a, b, c, d) :: T #

Methods

toVal :: (a, b, c, d) -> Value (ToT (a, b, c, d)) #

fromVal :: Value (ToT (a, b, c, d)) -> (a, b, c, d) #

(IsoValue a, IsoValue b, IsoValue c, IsoValue d, IsoValue e) => IsoValue (a, b, c, d, e) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (a, b, c, d, e) :: T #

Methods

toVal :: (a, b, c, d, e) -> Value (ToT (a, b, c, d, e)) #

fromVal :: Value (ToT (a, b, c, d, e)) -> (a, b, c, d, e) #

(IsoValue a, IsoValue b, IsoValue c, IsoValue d, IsoValue e, IsoValue f) => IsoValue (a, b, c, d, e, f) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (a, b, c, d, e, f) :: T #

Methods

toVal :: (a, b, c, d, e, f) -> Value (ToT (a, b, c, d, e, f)) #

fromVal :: Value (ToT (a, b, c, d, e, f)) -> (a, b, c, d, e, f) #

(IsoValue a, IsoValue b, IsoValue c, IsoValue d, IsoValue e, IsoValue f, IsoValue g) => IsoValue (a, b, c, d, e, f, g) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (a, b, c, d, e, f, g) :: T #

Methods

toVal :: (a, b, c, d, e, f, g) -> Value (ToT (a, b, c, d, e, f, g)) #

fromVal :: Value (ToT (a, b, c, d, e, f, g)) -> (a, b, c, d, e, f, g) #

type WellTypedIsoValue a = (WellTyped (ToT a), IsoValue a) #

Primitive types

data Integer #

Arbitrary precision integers. In contrast with fixed-size integral types such as Int, the Integer type represents the entire infinite range of integers.

For more information about this type's representation, see the comments in its implementation.

Instances

Instances details
Enum Integer

Since: base-2.1

Instance details

Defined in GHC.Enum

Eq Integer 
Instance details

Defined in GHC.Integer.Type

Methods

(==) :: Integer -> Integer -> Bool #

(/=) :: Integer -> Integer -> Bool #

Integral Integer

Since: base-2.0.1

Instance details

Defined in GHC.Real

Num Integer

Since: base-2.1

Instance details

Defined in GHC.Num

Ord Integer 
Instance details

Defined in GHC.Integer.Type

Read Integer

Since: base-2.1

Instance details

Defined in GHC.Read

Real Integer

Since: base-2.0.1

Instance details

Defined in GHC.Real

Show Integer

Since: base-2.1

Instance details

Defined in GHC.Show

Hashable Integer 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Integer -> Int #

hash :: Integer -> Int #

ToJSON Integer 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON TezosBigNum 
Instance details

Defined in Morley.Micheline.Json

Methods

toJSON :: TezosBigNum -> Value #

toEncoding :: TezosBigNum -> Encoding #

toJSONList :: [TezosBigNum] -> Value #

toEncodingList :: [TezosBigNum] -> Encoding #

ToJSONKey Integer 
Instance details

Defined in Data.Aeson.Types.ToJSON

FromJSON TezosBigNum 
Instance details

Defined in Morley.Micheline.Json

Methods

parseJSON :: Value -> Parser TezosBigNum #

parseJSONList :: Value -> Parser [TezosBigNum] #

Subtractive Integer 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Integer #

NFData Integer 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Integer -> () #

Default Integer 
Instance details

Defined in Data.Default.Class

Methods

def :: Integer #

Buildable Integer 
Instance details

Defined in Formatting.Buildable

Methods

build :: Integer -> Builder #

Semiring Integer 
Instance details

Defined in Data.Semiring

Ring Integer 
Instance details

Defined in Data.Semiring

Methods

negate :: Integer -> Integer #

Pretty Integer 
Instance details

Defined in Text.PrettyPrint.Leijen.Text

Methods

pretty :: Integer -> Doc #

prettyList :: [Integer] -> Doc #

TypeHasDoc Integer 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions Integer :: FieldDescriptions #

IsoValue Integer 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Integer :: T #

HasAnnotation Integer Source # 
Instance details

Defined in Lorentz.Annotation

NonZero Integer Source # 
Instance details

Defined in Lorentz.Instr

Methods

nonZero :: forall (s :: [Type]). (Integer ': s) :-> (Maybe Integer ': s) Source #

LDefault Integer Source # 
Instance details

Defined in Lorentz.Default

Methods

ldef :: Integer Source #

lIsDef :: forall (s :: [Type]). (Integer ': s) :-> (Bool ': s) Source #

Lift Integer 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Integer -> Q Exp #

liftTyped :: Integer -> Q (TExp Integer) #

MultiplyPoint Integer Bls12381G1 
Instance details

Defined in Tezos.Crypto.BLS12381

MultiplyPoint Integer Bls12381G2 
Instance details

Defined in Tezos.Crypto.BLS12381

EDivOpHs Integer Integer Source # 
Instance details

Defined in Lorentz.Polymorphic

EDivOpHs Integer Natural Source # 
Instance details

Defined in Lorentz.Polymorphic

EDivOpHs Natural Integer Source # 
Instance details

Defined in Lorentz.Polymorphic

UnaryArithOpHs Abs Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Abs Integer Source #

UnaryArithOpHs Eq' Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Eq' Integer Source #

UnaryArithOpHs Ge Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Ge Integer Source #

UnaryArithOpHs Gt Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Gt Integer Source #

UnaryArithOpHs Le Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Le Integer Source #

UnaryArithOpHs Lt Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Lt Integer Source #

UnaryArithOpHs Neg Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Neg Integer Source #

UnaryArithOpHs Neq Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Neq Integer Source #

UnaryArithOpHs Not Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Not Integer Source #

KnownNat n => Reifies (n :: Nat) Integer 
Instance details

Defined in Data.Reflection

Methods

reflect :: proxy n -> Integer #

ArithOpHs Add Integer Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Integer Integer Source #

ArithOpHs Add Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Integer Natural Source #

ArithOpHs Add Integer Timestamp Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Integer Timestamp Source #

ArithOpHs Add Natural Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Natural Integer Source #

ArithOpHs Add Timestamp Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Timestamp Integer Source #

ArithOpHs And Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs And Integer Natural Source #

ArithOpHs Mul Integer Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Integer Integer Source #

ArithOpHs Mul Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Integer Natural Source #

ArithOpHs Mul Integer Bls12381Fr Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Integer Bls12381Fr Source #

ArithOpHs Mul Natural Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Natural Integer Source #

ArithOpHs Mul Bls12381Fr Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Bls12381Fr Integer Source #

ArithOpHs Sub Integer Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Sub Integer Integer Source #

ArithOpHs Sub Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Sub Integer Natural Source #

ArithOpHs Sub Natural Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Sub Natural Integer Source #

ArithOpHs Sub Timestamp Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Sub Timestamp Integer Source #

() :=> (Enum Integer) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Enum Integer #

() :=> (Eq Integer) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Eq Integer #

() :=> (Integral Integer) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Integral Integer #

() :=> (Num Integer) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Num Integer #

() :=> (Ord Integer) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Ord Integer #

() :=> (Real Integer) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Real Integer #

() :=> (Bits Integer) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Bits Integer #

type Difference Integer 
Instance details

Defined in Basement.Numerical.Subtractive

type TypeDocFieldDescriptions Integer 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type ToT Integer 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT Integer = 'TInt
type EDivOpResHs Integer Integer Source # 
Instance details

Defined in Lorentz.Polymorphic

type EDivOpResHs Integer Natural Source # 
Instance details

Defined in Lorentz.Polymorphic

type EDivOpResHs Natural Integer Source # 
Instance details

Defined in Lorentz.Polymorphic

type EModOpResHs Integer Integer Source # 
Instance details

Defined in Lorentz.Polymorphic

type EModOpResHs Integer Natural Source # 
Instance details

Defined in Lorentz.Polymorphic

type EModOpResHs Natural Integer Source # 
Instance details

Defined in Lorentz.Polymorphic

type UnaryArithResHs Abs Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Eq' Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Ge Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Gt Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Le Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Lt Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Neg Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Neq Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Not Integer Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Add Integer Integer Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Add Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Add Integer Timestamp Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Add Natural Integer Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Add Timestamp Integer Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs And Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Mul Integer Integer Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Mul Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Mul Integer Bls12381Fr Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Mul Natural Integer Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Mul Bls12381Fr Integer Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Sub Integer Integer Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Sub Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Sub Natural Integer Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Sub Timestamp Integer Source # 
Instance details

Defined in Lorentz.Arith

data Natural #

Type representing arbitrary-precision non-negative integers.

>>> 2^100 :: Natural
1267650600228229401496703205376

Operations whose result would be negative throw (Underflow :: ArithException),

>>> -1 :: Natural
*** Exception: arithmetic underflow

Since: base-4.8.0.0

Instances

Instances details
Enum Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Enum

Eq Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Natural

Methods

(==) :: Natural -> Natural -> Bool #

(/=) :: Natural -> Natural -> Bool #

Integral Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Real

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

Ord Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Natural

Read Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Read

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

Hashable Natural 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Natural -> Int #

hash :: Natural -> Int #

ToJSON Natural 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON TezosNat 
Instance details

Defined in Morley.Micheline.Json

Methods

toJSON :: TezosNat -> Value #

toEncoding :: TezosNat -> Encoding #

toJSONList :: [TezosNat] -> Value #

toEncodingList :: [TezosNat] -> Encoding #

ToJSONKey Natural 
Instance details

Defined in Data.Aeson.Types.ToJSON

FromJSON TezosNat 
Instance details

Defined in Morley.Micheline.Json

Methods

parseJSON :: Value -> Parser TezosNat #

parseJSONList :: Value -> Parser [TezosNat] #

Subtractive Natural 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Natural #

NFData Natural

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Natural -> () #

Buildable TezosNat 
Instance details

Defined in Morley.Micheline.Json

Methods

build :: TezosNat -> Builder #

Semiring Natural 
Instance details

Defined in Data.Semiring

TypeHasDoc Natural 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions Natural :: FieldDescriptions #

IsoValue Natural 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Natural :: T #

HasAnnotation Natural Source # 
Instance details

Defined in Lorentz.Annotation

ToIntegerArithOpHs Natural Source # 
Instance details

Defined in Lorentz.Arith

NonZero Natural Source # 
Instance details

Defined in Lorentz.Instr

Methods

nonZero :: forall (s :: [Type]). (Natural ': s) :-> (Maybe Natural ': s) Source #

LDefault Natural Source # 
Instance details

Defined in Lorentz.Default

Methods

ldef :: Natural Source #

lIsDef :: forall (s :: [Type]). (Natural ': s) :-> (Bool ': s) Source #

Lift Natural 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Natural -> Q Exp #

liftTyped :: Natural -> Q (TExp Natural) #

EDivOpHs Integer Natural Source # 
Instance details

Defined in Lorentz.Polymorphic

EDivOpHs Natural Integer Source # 
Instance details

Defined in Lorentz.Polymorphic

EDivOpHs Natural Natural Source # 
Instance details

Defined in Lorentz.Polymorphic

EDivOpHs Mutez Natural Source # 
Instance details

Defined in Lorentz.Polymorphic

UnaryArithOpHs Neg Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Neg Natural Source #

UnaryArithOpHs Not Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Not Natural Source #

ArithOpHs Add Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Integer Natural Source #

ArithOpHs Add Natural Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Natural Integer Source #

ArithOpHs Add Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Natural Natural Source #

ArithOpHs And Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs And Integer Natural Source #

ArithOpHs And Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs And Natural Natural Source #

ArithOpHs Lsl Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Lsl Natural Natural Source #

ArithOpHs Lsr Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Lsr Natural Natural Source #

ArithOpHs Mul Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Integer Natural Source #

ArithOpHs Mul Natural Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Natural Integer Source #

ArithOpHs Mul Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Natural Natural Source #

ArithOpHs Mul Natural Bls12381Fr Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Natural Bls12381Fr Source #

ArithOpHs Mul Natural Mutez Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Natural Mutez Source #

ArithOpHs Mul Bls12381Fr Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Bls12381Fr Natural Source #

ArithOpHs Mul Mutez Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Mutez Natural Source #

ArithOpHs Or Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Or Natural Natural Source #

ArithOpHs Sub Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Sub Integer Natural Source #

ArithOpHs Sub Natural Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Sub Natural Integer Source #

ArithOpHs Sub Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Sub Natural Natural Source #

ArithOpHs Xor Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Xor Natural Natural Source #

() :=> (Enum Natural) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Enum Natural #

() :=> (Eq Natural) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Eq Natural #

() :=> (Integral Natural) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Integral Natural #

() :=> (Num Natural) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Num Natural #

() :=> (Ord Natural) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Ord Natural #

() :=> (Read Natural) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Read Natural #

() :=> (Real Natural) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Real Natural #

() :=> (Show Natural) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Show Natural #

() :=> (Bits Natural) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Bits Natural #

type Difference Natural 
Instance details

Defined in Basement.Numerical.Subtractive

type TypeDocFieldDescriptions Natural 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type ToT Natural 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT Natural = 'TNat
type EDivOpResHs Integer Natural Source # 
Instance details

Defined in Lorentz.Polymorphic

type EDivOpResHs Natural Integer Source # 
Instance details

Defined in Lorentz.Polymorphic

type EDivOpResHs Natural Natural Source # 
Instance details

Defined in Lorentz.Polymorphic

type EDivOpResHs Mutez Natural Source # 
Instance details

Defined in Lorentz.Polymorphic

type EModOpResHs Integer Natural Source # 
Instance details

Defined in Lorentz.Polymorphic

type EModOpResHs Natural Integer Source # 
Instance details

Defined in Lorentz.Polymorphic

type EModOpResHs Natural Natural Source # 
Instance details

Defined in Lorentz.Polymorphic

type EModOpResHs Mutez Natural Source # 
Instance details

Defined in Lorentz.Polymorphic

type UnaryArithResHs Neg Natural Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Not Natural Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Add Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Add Natural Integer Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Add Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs And Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs And Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Lsl Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Lsr Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Mul Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Mul Natural Integer Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Mul Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Mul Natural Bls12381Fr Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Mul Natural Mutez Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Mul Bls12381Fr Natural Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Mul Mutez Natural Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Or Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Sub Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Sub Natural Integer Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Sub Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Xor Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

data MText #

Instances

Instances details
Eq MText 
Instance details

Defined in Michelson.Text

Methods

(==) :: MText -> MText -> Bool #

(/=) :: MText -> MText -> Bool #

Data MText 
Instance details

Defined in Michelson.Text

Methods

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

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

toConstr :: MText -> Constr #

dataTypeOf :: MText -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord MText 
Instance details

Defined in Michelson.Text

Methods

compare :: MText -> MText -> Ordering #

(<) :: MText -> MText -> Bool #

(<=) :: MText -> MText -> Bool #

(>) :: MText -> MText -> Bool #

(>=) :: MText -> MText -> Bool #

max :: MText -> MText -> MText #

min :: MText -> MText -> MText #

Show MText 
Instance details

Defined in Michelson.Text

Methods

showsPrec :: Int -> MText -> ShowS #

show :: MText -> String #

showList :: [MText] -> ShowS #

Generic MText 
Instance details

Defined in Michelson.Text

Associated Types

type Rep MText :: Type -> Type #

Methods

from :: MText -> Rep MText x #

to :: Rep MText x -> MText #

Semigroup MText 
Instance details

Defined in Michelson.Text

Methods

(<>) :: MText -> MText -> MText #

sconcat :: NonEmpty MText -> MText #

stimes :: Integral b => b -> MText -> MText #

Monoid MText 
Instance details

Defined in Michelson.Text

Methods

mempty :: MText #

mappend :: MText -> MText -> MText #

mconcat :: [MText] -> MText #

Hashable MText 
Instance details

Defined in Michelson.Text

Methods

hashWithSalt :: Int -> MText -> Int #

hash :: MText -> Int #

ToJSON MText 
Instance details

Defined in Michelson.Text

FromJSON MText 
Instance details

Defined in Michelson.Text

NFData MText 
Instance details

Defined in Michelson.Text

Methods

rnf :: MText -> () #

Buildable MText 
Instance details

Defined in Michelson.Text

Methods

build :: MText -> Builder #

ToText MText 
Instance details

Defined in Michelson.Text

Methods

toText :: MText -> Text #

Container MText 
Instance details

Defined in Michelson.Text

Associated Types

type Element MText #

Methods

toList :: MText -> [Element MText] #

null :: MText -> Bool #

foldr :: (Element MText -> b -> b) -> b -> MText -> b #

foldl :: (b -> Element MText -> b) -> b -> MText -> b #

foldl' :: (b -> Element MText -> b) -> b -> MText -> b #

length :: MText -> Int #

elem :: Element MText -> MText -> Bool #

maximum :: MText -> Element MText #

minimum :: MText -> Element MText #

foldMap :: Monoid m => (Element MText -> m) -> MText -> m #

fold :: MText -> Element MText #

foldr' :: (Element MText -> b -> b) -> b -> MText -> b #

foldr1 :: (Element MText -> Element MText -> Element MText) -> MText -> Element MText #

foldl1 :: (Element MText -> Element MText -> Element MText) -> MText -> Element MText #

notElem :: Element MText -> MText -> Bool #

all :: (Element MText -> Bool) -> MText -> Bool #

any :: (Element MText -> Bool) -> MText -> Bool #

and :: MText -> Bool #

or :: MText -> Bool #

find :: (Element MText -> Bool) -> MText -> Maybe (Element MText) #

safeHead :: MText -> Maybe (Element MText) #

HasCLReader MText 
Instance details

Defined in Michelson.Text

TypeHasDoc MText 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions MText :: FieldDescriptions #

IsoValue MText 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT MText :: T #

HasAnnotation MText Source # 
Instance details

Defined in Lorentz.Annotation

SliceOpHs MText Source # 
Instance details

Defined in Lorentz.Polymorphic

ConcatOpHs MText Source # 
Instance details

Defined in Lorentz.Polymorphic

SizeOpHs MText Source # 
Instance details

Defined in Lorentz.Polymorphic

IsCustomErrorArgRep MText Source # 
Instance details

Defined in Lorentz.Errors

ErrorHasDoc MText Source # 
Instance details

Defined in Lorentz.Errors

Associated Types

type ErrorRequirements MText Source #

IsError MText Source #

Use this for internal errors only.

Normal error scenarios should use the mechanism of custom errors, see below.

Instance details

Defined in Lorentz.Errors

Methods

errorToVal :: MText -> (forall (t :: T). ErrorScope t => Value t -> r) -> r Source #

errorFromVal :: forall (t :: T). KnownT t => Value t -> Either Text MText Source #

TypeHasDoc errArg => IsCustomErrorArgRep (MText, errArg) Source # 
Instance details

Defined in Lorentz.Errors

type Rep MText 
Instance details

Defined in Michelson.Text

type Rep MText = D1 ('MetaData "MText" "Michelson.Text" "morley-1.14.0-inplace" 'True) (C1 ('MetaCons "MTextUnsafe" 'PrefixI 'True) (S1 ('MetaSel ('Just "unMText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))
type Element MText 
Instance details

Defined in Michelson.Text

type TypeDocFieldDescriptions MText 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type ToT MText 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT MText = 'TString
type ErrorRequirements MText Source # 
Instance details

Defined in Lorentz.Errors

data Bool #

Constructors

False 
True 

Instances

Instances details
Bounded Bool

Since: base-2.1

Instance details

Defined in GHC.Enum

Enum Bool

Since: base-2.1

Instance details

Defined in GHC.Enum

Methods

succ :: Bool -> Bool #

pred :: Bool -> Bool #

toEnum :: Int -> Bool #

fromEnum :: Bool -> Int #

enumFrom :: Bool -> [Bool] #

enumFromThen :: Bool -> Bool -> [Bool] #

enumFromTo :: Bool -> Bool -> [Bool] #

enumFromThenTo :: Bool -> Bool -> Bool -> [Bool] #

Eq Bool 
Instance details

Defined in GHC.Classes

Methods

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

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

Ord Bool 
Instance details

Defined in GHC.Classes

Methods

compare :: Bool -> Bool -> Ordering #

(<) :: Bool -> Bool -> Bool #

(<=) :: Bool -> Bool -> Bool #

(>) :: Bool -> Bool -> Bool #

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

max :: Bool -> Bool -> Bool #

min :: Bool -> Bool -> Bool #

Read Bool

Since: base-2.1

Instance details

Defined in GHC.Read

Show Bool

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> Bool -> ShowS #

show :: Bool -> String #

showList :: [Bool] -> ShowS #

Generic Bool

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep Bool :: Type -> Type #

Methods

from :: Bool -> Rep Bool x #

to :: Rep Bool x -> Bool #

Hashable Bool 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Bool -> Int #

hash :: Bool -> Int #

ToJSON Bool 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Bool 
Instance details

Defined in Data.Aeson.Types.ToJSON

Storable Bool

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Bool -> Int #

alignment :: Bool -> Int #

peekElemOff :: Ptr Bool -> Int -> IO Bool #

pokeElemOff :: Ptr Bool -> Int -> Bool -> IO () #

peekByteOff :: Ptr b -> Int -> IO Bool #

pokeByteOff :: Ptr b -> Int -> Bool -> IO () #

peek :: Ptr Bool -> IO Bool #

poke :: Ptr Bool -> Bool -> IO () #

NFData Bool 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Bool -> () #

Buildable Bool 
Instance details

Defined in Formatting.Buildable

Methods

build :: Bool -> Builder #

Unbox Bool 
Instance details

Defined in Data.Vector.Unboxed.Base

Semiring Bool 
Instance details

Defined in Data.Semiring

Methods

plus :: Bool -> Bool -> Bool #

zero :: Bool #

times :: Bool -> Bool -> Bool #

one :: Bool #

fromNatural :: Natural -> Bool #

PShow Bool 
Instance details

Defined in Data.Singletons.Prelude.Show

Associated Types

type ShowsPrec arg arg1 arg2 :: Symbol #

type Show_ arg :: Symbol #

type ShowList arg arg1 :: Symbol #

SShow Bool 
Instance details

Defined in Data.Singletons.Prelude.Show

Methods

sShowsPrec :: forall (t1 :: Nat) (t2 :: Bool) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply ShowsPrecSym0 t1) t2) t3) #

sShow_ :: forall (t :: Bool). Sing t -> Sing (Apply Show_Sym0 t) #

sShowList :: forall (t1 :: [Bool]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply ShowListSym0 t1) t2) #

PEnum Bool 
Instance details

Defined in Data.Singletons.Prelude.Enum

Associated Types

type Succ arg :: a #

type Pred arg :: a #

type ToEnum arg :: a #

type FromEnum arg :: Nat #

type EnumFromTo arg arg1 :: [a] #

type EnumFromThenTo arg arg1 arg2 :: [a] #

SEnum Bool 
Instance details

Defined in Data.Singletons.Prelude.Enum

Methods

sSucc :: forall (t :: Bool). Sing t -> Sing (Apply SuccSym0 t) #

sPred :: forall (t :: Bool). Sing t -> Sing (Apply PredSym0 t) #

sToEnum :: forall (t :: Nat). Sing t -> Sing (Apply ToEnumSym0 t) #

sFromEnum :: forall (t :: Bool). Sing t -> Sing (Apply FromEnumSym0 t) #

sEnumFromTo :: forall (t1 :: Bool) (t2 :: Bool). Sing t1 -> Sing t2 -> Sing (Apply (Apply EnumFromToSym0 t1) t2) #

sEnumFromThenTo :: forall (t1 :: Bool) (t2 :: Bool) (t3 :: Bool). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply EnumFromThenToSym0 t1) t2) t3) #

PBounded Bool 
Instance details

Defined in Data.Singletons.Prelude.Enum

Associated Types

type MinBound :: a #

type MaxBound :: a #

SBounded Bool 
Instance details

Defined in Data.Singletons.Prelude.Enum

POrd Bool 
Instance details

Defined in Data.Singletons.Prelude.Ord

Associated Types

type Compare arg arg1 :: Ordering #

type arg < arg1 :: Bool #

type arg <= arg1 :: Bool #

type arg > arg1 :: Bool #

type arg >= arg1 :: Bool #

type Max arg arg1 :: a #

type Min arg arg1 :: a #

SOrd Bool 
Instance details

Defined in Data.Singletons.Prelude.Ord

Methods

sCompare :: forall (t1 :: Bool) (t2 :: Bool). Sing t1 -> Sing t2 -> Sing (Apply (Apply CompareSym0 t1) t2) #

(%<) :: forall (t1 :: Bool) (t2 :: Bool). Sing t1 -> Sing t2 -> Sing (Apply (Apply (<@#@$) t1) t2) #

(%<=) :: forall (t1 :: Bool) (t2 :: Bool). Sing t1 -> Sing t2 -> Sing (Apply (Apply (<=@#@$) t1) t2) #

(%>) :: forall (t1 :: Bool) (t2 :: Bool). Sing t1 -> Sing t2 -> Sing (Apply (Apply (>@#@$) t1) t2) #

(%>=) :: forall (t1 :: Bool) (t2 :: Bool). Sing t1 -> Sing t2 -> Sing (Apply (Apply (>=@#@$) t1) t2) #

sMax :: forall (t1 :: Bool) (t2 :: Bool). Sing t1 -> Sing t2 -> Sing (Apply (Apply MaxSym0 t1) t2) #

sMin :: forall (t1 :: Bool) (t2 :: Bool). Sing t1 -> Sing t2 -> Sing (Apply (Apply MinSym0 t1) t2) #

SEq Bool 
Instance details

Defined in Data.Singletons.Prelude.Eq

Methods

(%==) :: forall (a :: Bool) (b :: Bool). Sing a -> Sing b -> Sing (a == b) #

(%/=) :: forall (a :: Bool) (b :: Bool). Sing a -> Sing b -> Sing (a /= b) #

PEq Bool 
Instance details

Defined in Data.Singletons.Prelude.Eq

Associated Types

type x == y :: Bool #

type x /= y :: Bool #

Pretty Bool 
Instance details

Defined in Text.PrettyPrint.Leijen.Text

Methods

pretty :: Bool -> Doc #

prettyList :: [Bool] -> Doc #

SingKind Bool

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type DemoteRep Bool

Methods

fromSing :: forall (a :: Bool). Sing a -> DemoteRep Bool

TypeHasDoc Bool 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions Bool :: FieldDescriptions #

IsoValue Bool 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Bool :: T #

Methods

toVal :: Bool -> Value (ToT Bool) #

fromVal :: Value (ToT Bool) -> Bool #

HasAnnotation Bool Source # 
Instance details

Defined in Lorentz.Annotation

Lift Bool 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Bool -> Q Exp #

liftTyped :: Bool -> Q (TExp Bool) #

TestCoercion SBool 
Instance details

Defined in Data.Singletons.Prelude.Instances

Methods

testCoercion :: forall (a :: k) (b :: k). SBool a -> SBool b -> Maybe (Coercion a b) #

TestEquality SBool 
Instance details

Defined in Data.Singletons.Prelude.Instances

Methods

testEquality :: forall (a :: k) (b :: k). SBool a -> SBool b -> Maybe (a :~: b) #

Vector Vector Bool 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Bool 
Instance details

Defined in Data.Vector.Unboxed.Base

SingI 'False

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing 'False

SingI 'True

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing 'True

UnaryArithOpHs Not Bool Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Not Bool Source #

ArithOpHs And Bool Bool Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs And Bool Bool Source #

ArithOpHs Or Bool Bool Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Or Bool Bool Source #

ArithOpHs Xor Bool Bool Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Xor Bool Bool Source #

() :=> (Bounded Bool) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Bounded Bool #

() :=> (Enum Bool) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Enum Bool #

() :=> (Eq Bool) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Eq Bool #

() :=> (Ord Bool) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Ord Bool #

() :=> (Read Bool) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Read Bool #

() :=> (Show Bool) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Show Bool #

() :=> (Bits Bool) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Bits Bool #

SuppressUnusedWarnings NotSym0 
Instance details

Defined in Data.Singletons.Prelude.Bool

SuppressUnusedWarnings FromEnum_6989586621680203592Sym0 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings All_Sym0 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal.Disambiguation

SuppressUnusedWarnings AllSym0 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

SuppressUnusedWarnings Any_Sym0 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal.Disambiguation

SuppressUnusedWarnings AnySym0 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

SuppressUnusedWarnings (||@#@$) 
Instance details

Defined in Data.Singletons.Prelude.Bool

SuppressUnusedWarnings (&&@#@$) 
Instance details

Defined in Data.Singletons.Prelude.Bool

SuppressUnusedWarnings Compare_6989586621679848336Sym0 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings ShowParenSym0 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings OrSym0 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings AndSym0 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings ToEnum_6989586621680203579Sym0 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings ShowsPrec_6989586621680653401Sym0 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings (<=?@#@$) 
Instance details

Defined in Data.Singletons.TypeLits.Internal

SuppressUnusedWarnings GetAllSym0 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

SuppressUnusedWarnings GetAnySym0 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

SingI NotSym0 
Instance details

Defined in Data.Singletons.Prelude.Bool

Methods

sing :: Sing NotSym0 #

SingI (||@#@$) 
Instance details

Defined in Data.Singletons.Prelude.Bool

Methods

sing :: Sing (||@#@$) #

SingI (&&@#@$) 
Instance details

Defined in Data.Singletons.Prelude.Bool

Methods

sing :: Sing (&&@#@$) #

SingI (<=?@#@$) 
Instance details

Defined in Data.Singletons.TypeLits.Internal

Methods

sing :: Sing (<=?@#@$) #

SingI All_Sym0 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal.Disambiguation

Methods

sing :: Sing All_Sym0 #

SingI AllSym0 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

sing :: Sing AllSym0 #

SingI Any_Sym0 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal.Disambiguation

Methods

sing :: Sing Any_Sym0 #

SingI AnySym0 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

sing :: Sing AnySym0 #

SingI ShowParenSym0 
Instance details

Defined in Data.Singletons.Prelude.Show

SingI OrSym0 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing OrSym0 #

SingI AndSym0 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing AndSym0 #

SingI GetAllSym0 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

sing :: Sing GetAllSym0 #

SingI GetAnySym0 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

sing :: Sing GetAnySym0 #

SuppressUnusedWarnings ((||@#@$$) a6989586621679815663 :: TyFun Bool Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Bool

SuppressUnusedWarnings ((&&@#@$$) a6989586621679815361 :: TyFun Bool Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Bool

SuppressUnusedWarnings (Compare_6989586621679848336Sym1 a6989586621679848341 :: TyFun Bool Ordering -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (GuardSym0 :: TyFun Bool (f ()) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (ShowsPrec_6989586621680653401Sym1 a6989586621680653411 :: TyFun Bool (Symbol ~> Symbol) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings (UnlessSym0 :: TyFun Bool (f () ~> f ()) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad

SuppressUnusedWarnings (WhenSym0 :: TyFun Bool (f () ~> f ()) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (ListnullSym0 :: TyFun [a] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal.Disambiguation

SuppressUnusedWarnings (ListisPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal.Disambiguation

SuppressUnusedWarnings (NullSym0 :: TyFun [a] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Null_6989586621680822604Sym0 :: TyFun [a] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (IsNothingSym0 :: TyFun (Maybe a) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (IsJustSym0 :: TyFun (Maybe a) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings ((<=?@#@$$) a6989586621679910080 :: TyFun Nat Bool -> Type) 
Instance details

Defined in Data.Singletons.TypeLits.Internal

SuppressUnusedWarnings (ListelemSym0 :: TyFun a ([a] ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal.Disambiguation

SuppressUnusedWarnings (NotElemSym0 :: TyFun a ([a] ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (ElemSym0 :: TyFun a ([a] ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (OrSym0 :: TyFun (t Bool) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680813469Scrutinee_6989586621680813411Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680813445Scrutinee_6989586621680813409Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680823228Sym0 :: TyFun a (Product a ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680823053Sym0 :: TyFun a (Sum a ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680822878Sym0 :: TyFun a (Dual a ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680822846Sym0 :: TyFun a (Proxy a ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680822470Sym0 :: TyFun a ([a] ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (AndSym0 :: TyFun (t Bool) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (DefaultEqSym0 :: TyFun k (k ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Eq

SuppressUnusedWarnings ((==@#@$) :: TyFun a (a ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Eq

SuppressUnusedWarnings ((/=@#@$) :: TyFun a (a ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Eq

SuppressUnusedWarnings (Bool_Sym0 :: TyFun a (a ~> (Bool ~> a)) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Bool

SuppressUnusedWarnings (TFHelper_6989586621679836822Sym0 :: TyFun a (a ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (TFHelper_6989586621679836806Sym0 :: TyFun a (a ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (TFHelper_6989586621679836790Sym0 :: TyFun a (a ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (TFHelper_6989586621679836774Sym0 :: TyFun a (a ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (Let6989586621679836863Scrutinee_6989586621679836691Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (Let6989586621679836847Scrutinee_6989586621679836689Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (Let6989586621679836766Scrutinee_6989586621679836679Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (Let6989586621679836762Scrutinee_6989586621679836677Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings ((>@#@$) :: TyFun a (a ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings ((>=@#@$) :: TyFun a (a ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings ((<@#@$) :: TyFun a (a ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings ((<=@#@$) :: TyFun a (a ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (Let6989586621680786609Scrutinee_6989586621680786014Sym0 :: TyFun k1 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Proxy

SuppressUnusedWarnings (Elem_6989586621681011897Sym0 :: TyFun a (Identity a ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Identity

SuppressUnusedWarnings (Null_6989586621681012013Sym0 :: TyFun (Identity a) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Identity

SuppressUnusedWarnings (Null_6989586621680823010Sym0 :: TyFun (Dual a) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Null_6989586621680823185Sym0 :: TyFun (Sum a) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Null_6989586621680823360Sym0 :: TyFun (Product a) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (ListtakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal.Disambiguation

SuppressUnusedWarnings (ListspanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal.Disambiguation

SuppressUnusedWarnings (ListpartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal.Disambiguation

SuppressUnusedWarnings (ListnubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal.Disambiguation

SuppressUnusedWarnings (ListfilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal.Disambiguation

SuppressUnusedWarnings (ListdropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal.Disambiguation

SuppressUnusedWarnings (UnionBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (SelectSym0 :: TyFun (a ~> Bool) (a ~> (([a], [a]) ~> ([a], [a]))) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680378869ZsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680378869YsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680378869X_6989586621680378870Sym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] ([k], [k]) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680378834ZsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680378834YsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680378834X_6989586621680378835Sym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] ([k], [k]) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (FindSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Nat]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Nat) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Elem_bySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> Bool)) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (AnySym0 :: TyFun (a ~> Bool) ([a] ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (AllSym0 :: TyFun (a ~> Bool) ([a] ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (UntilSym0 :: TyFun (a ~> Bool) ((a ~> a) ~> (a ~> a)) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Base

SingI x => SingI ((||@#@$$) x :: TyFun Bool Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Bool

Methods

sing :: Sing ((||@#@$$) x) #

SingI x => SingI ((&&@#@$$) x :: TyFun Bool Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Bool

Methods

sing :: Sing ((&&@#@$$) x) #

SingI x => SingI ((<=?@#@$$) x :: TyFun Nat Bool -> Type) 
Instance details

Defined in Data.Singletons.TypeLits.Internal

Methods

sing :: Sing ((<=?@#@$$) x) #

SAlternative f => SingI (GuardSym0 :: TyFun Bool (f ()) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

Methods

sing :: Sing GuardSym0 #

SApplicative f => SingI (UnlessSym0 :: TyFun Bool (f () ~> f ()) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad

Methods

sing :: Sing UnlessSym0 #

SApplicative f => SingI (WhenSym0 :: TyFun Bool (f () ~> f ()) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

Methods

sing :: Sing WhenSym0 #

SingI (ListnullSym0 :: TyFun [a] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal.Disambiguation

Methods

sing :: Sing ListnullSym0 #

SEq a => SingI (ListisPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal.Disambiguation

Methods

sing :: Sing ListisPrefixOfSym0 #

SingI (NullSym0 :: TyFun [a] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing NullSym0 #

SEq a => SingI (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SEq a => SingI (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SEq a => SingI (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SingI (IsNothingSym0 :: TyFun (Maybe a) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SingI (IsJustSym0 :: TyFun (Maybe a) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

Methods

sing :: Sing IsJustSym0 #

SEq a => SingI (ListelemSym0 :: TyFun a ([a] ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal.Disambiguation

Methods

sing :: Sing ListelemSym0 #

SEq a => SingI (NotElemSym0 :: TyFun a ([a] ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing NotElemSym0 #

SEq a => SingI (ElemSym0 :: TyFun a ([a] ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing ElemSym0 #

SFoldable t => SingI (OrSym0 :: TyFun (t Bool) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing OrSym0 #

SFoldable t => SingI (AndSym0 :: TyFun (t Bool) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing AndSym0 #

SEq a => SingI ((==@#@$) :: TyFun a (a ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Eq

Methods

sing :: Sing (==@#@$) #

SEq a => SingI ((/=@#@$) :: TyFun a (a ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Eq

Methods

sing :: Sing (/=@#@$) #

SingI (Bool_Sym0 :: TyFun a (a ~> (Bool ~> a)) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Bool

Methods

sing :: Sing Bool_Sym0 #

SOrd a => SingI ((>@#@$) :: TyFun a (a ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

Methods

sing :: Sing (>@#@$) #

SOrd a => SingI ((>=@#@$) :: TyFun a (a ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

Methods

sing :: Sing (>=@#@$) #

SOrd a => SingI ((<@#@$) :: TyFun a (a ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

Methods

sing :: Sing (<@#@$) #

SOrd a => SingI ((<=@#@$) :: TyFun a (a ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

Methods

sing :: Sing (<=@#@$) #

SingI (ListtakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal.Disambiguation

Methods

sing :: Sing ListtakeWhileSym0 #

SingI (ListspanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal.Disambiguation

Methods

sing :: Sing ListspanSym0 #

SingI (ListpartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal.Disambiguation

Methods

sing :: Sing ListpartitionSym0 #

SingI (ListnubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal.Disambiguation

Methods

sing :: Sing ListnubBySym0 #

SingI (ListfilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal.Disambiguation

Methods

sing :: Sing ListfilterSym0 #

SingI (ListdropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal.Disambiguation

Methods

sing :: Sing ListdropWhileSym0 #

SingI (UnionBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SingI (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SingI (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing SpanSym0 #

SingI (SelectSym0 :: TyFun (a ~> Bool) (a ~> (([a], [a]) ~> ([a], [a]))) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing SelectSym0 #

SingI (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SingI (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing NubBySym0 #

SingI (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SingI (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SingI (FindSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing FindSym0 #

SingI (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Nat]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SingI (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Nat) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SingI (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing FilterSym0 #

SingI (Elem_bySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> Bool)) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing Elem_bySym0 #

SingI (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SingI (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SingI (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SingI (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SingI (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing BreakSym0 #

SingI (AnySym0 :: TyFun (a ~> Bool) ([a] ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing AnySym0 #

SingI (AllSym0 :: TyFun (a ~> Bool) ([a] ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing AllSym0 #

SingI (UntilSym0 :: TyFun (a ~> Bool) ((a ~> a) ~> (a ~> a)) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Base

Methods

sing :: Sing UntilSym0 #

SuppressUnusedWarnings (ListisPrefixOfSym1 a6989586621680748854 :: TyFun [a] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal.Disambiguation

SuppressUnusedWarnings (ListelemSym1 a6989586621680748782 :: TyFun [a] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal.Disambiguation

SuppressUnusedWarnings (NotElemSym1 a6989586621680379352 :: TyFun [a] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (IsSuffixOfSym1 a6989586621680379375 :: TyFun [a] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (IsPrefixOfSym1 a6989586621680379382 :: TyFun [a] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (IsInfixOfSym1 a6989586621680379368 :: TyFun [a] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (ElemSym1 a6989586621680379360 :: TyFun [a] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (AnySym1 a6989586621680379577 :: TyFun [a] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (AllSym1 a6989586621680379585 :: TyFun [a] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Elem_6989586621680822470Sym1 a6989586621680822479 :: TyFun [a] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Null_6989586621680822765Sym0 :: TyFun (Either a1 a2) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (IsRightSym0 :: TyFun (Either a b) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Either

SuppressUnusedWarnings (IsLeftSym0 :: TyFun (Either a b) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Either

SuppressUnusedWarnings (Let6989586621680378657Scrutinee_6989586621680375102Sym0 :: TyFun k1 (TyFun k Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Elem_bySym1 a6989586621680378588 :: TyFun a ([a] ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680813469Scrutinee_6989586621680813411Sym1 x6989586621680813464 :: TyFun k1 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680813445Scrutinee_6989586621680813409Sym1 x6989586621680813440 :: TyFun k1 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680822360Sym0 :: TyFun a (t a ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (DefaultEqSym1 a6989586621679818750 :: TyFun k Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Eq

SuppressUnusedWarnings ((==@#@$$) a6989586621679818744 :: TyFun a Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Eq

SuppressUnusedWarnings ((/=@#@$$) a6989586621679818747 :: TyFun a Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Eq

SuppressUnusedWarnings (Bool_Sym1 a6989586621679814557 :: TyFun a (Bool ~> a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Bool

SuppressUnusedWarnings (TFHelper_6989586621679836822Sym1 a6989586621679836827 :: TyFun a Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (TFHelper_6989586621679836806Sym1 a6989586621679836811 :: TyFun a Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (TFHelper_6989586621679836790Sym1 a6989586621679836795 :: TyFun a Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (TFHelper_6989586621679836774Sym1 a6989586621679836779 :: TyFun a Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (Let6989586621679836863Scrutinee_6989586621679836691Sym1 x6989586621679836861 :: TyFun k1 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (Let6989586621679836847Scrutinee_6989586621679836689Sym1 x6989586621679836845 :: TyFun k1 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (Let6989586621679836766Scrutinee_6989586621679836679Sym1 x6989586621679836760 :: TyFun k1 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (Let6989586621679836762Scrutinee_6989586621679836677Sym1 x6989586621679836760 :: TyFun k1 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings ((>@#@$$) a6989586621679836734 :: TyFun a Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings ((>=@#@$$) a6989586621679836739 :: TyFun a Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings ((<@#@$$) a6989586621679836724 :: TyFun a Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings ((<=@#@$$) a6989586621679836729 :: TyFun a Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (TFHelper_6989586621681202942Sym0 :: TyFun (Arg a b) (Arg a b ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

SuppressUnusedWarnings (Elem_6989586621681011897Sym1 a6989586621681011902 :: TyFun (Identity a) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Identity

SuppressUnusedWarnings (Elem_6989586621680822878Sym1 a6989586621680822887 :: TyFun (Dual a) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680823053Sym1 a6989586621680823062 :: TyFun (Sum a) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680823228Sym1 a6989586621680823237 :: TyFun (Product a) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680822846Sym1 a6989586621680822851 :: TyFun (Proxy a) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Null_6989586621680822839Sym0 :: TyFun (Proxy a) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (TFHelper_6989586621680786553Sym0 :: TyFun (Proxy s) (Proxy s ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Proxy

SuppressUnusedWarnings (MfilterSym0 :: TyFun (a ~> Bool) (m a ~> m a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad

SuppressUnusedWarnings (FilterMSym0 :: TyFun (a ~> m Bool) ([a] ~> m [a]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad

SuppressUnusedWarnings (Let6989586621680378736ZsSym0 :: TyFun (k1 ~> (a ~> Bool)) (TyFun k1 (TyFun [a] [a] -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680378736YsSym0 :: TyFun (k1 ~> (a ~> Bool)) (TyFun k1 (TyFun [a] [a] -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680378736X_6989586621680378737Sym0 :: TyFun (k1 ~> (a ~> Bool)) (TyFun k1 (TyFun [a] ([a], [a]) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680378602NubBy'Sym0 :: TyFun (k1 ~> (k1 ~> Bool)) (TyFun k (TyFun [k1] ([k1] ~> [k1]) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Lambda_6989586621680378897Sym0 :: TyFun (a ~> Bool) (TyFun k (TyFun a (TyFun [a] [a] -> Type) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Lambda_6989586621680821893Sym0 :: TyFun (a ~> Bool) (TyFun k (TyFun a (First a) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621679989623GoSym0 :: TyFun (k1 ~> Bool) (TyFun (k1 ~> k1) (TyFun k2 (TyFun k1 k1 -> Type) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Base

(SEq a, SingI d) => SingI (ListisPrefixOfSym1 d :: TyFun [a] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal.Disambiguation

Methods

sing :: Sing (ListisPrefixOfSym1 d) #

(SEq a, SingI d) => SingI (ListelemSym1 d :: TyFun [a] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal.Disambiguation

Methods

sing :: Sing (ListelemSym1 d) #

(SEq a, SingI d) => SingI (NotElemSym1 d :: TyFun [a] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (NotElemSym1 d) #

(SEq a, SingI d) => SingI (IsSuffixOfSym1 d :: TyFun [a] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (IsSuffixOfSym1 d) #

(SEq a, SingI d) => SingI (IsPrefixOfSym1 d :: TyFun [a] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (IsPrefixOfSym1 d) #

(SEq a, SingI d) => SingI (IsInfixOfSym1 d :: TyFun [a] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (IsInfixOfSym1 d) #

(SEq a, SingI d) => SingI (ElemSym1 d :: TyFun [a] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (ElemSym1 d) #

SingI d => SingI (AnySym1 d :: TyFun [a] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (AnySym1 d) #

SingI d => SingI (AllSym1 d :: TyFun [a] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (AllSym1 d) #

SingI (IsRightSym0 :: TyFun (Either a b) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Either

SingI (IsLeftSym0 :: TyFun (Either a b) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Either

Methods

sing :: Sing IsLeftSym0 #

SingI d => SingI (Elem_bySym1 d :: TyFun a ([a] ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (Elem_bySym1 d) #

(SFoldable t, SEq a) => SingI (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

(SFoldable t, SEq a) => SingI (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing ElemSym0 #

(SEq a, SingI x) => SingI ((==@#@$$) x :: TyFun a Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Eq

Methods

sing :: Sing ((==@#@$$) x) #

(SEq a, SingI x) => SingI ((/=@#@$$) x :: TyFun a Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Eq

Methods

sing :: Sing ((/=@#@$$) x) #

SingI d => SingI (Bool_Sym1 d :: TyFun a (Bool ~> a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Bool

Methods

sing :: Sing (Bool_Sym1 d) #

(SOrd a, SingI d) => SingI ((>@#@$$) d :: TyFun a Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

Methods

sing :: Sing ((>@#@$$) d) #

(SOrd a, SingI d) => SingI ((>=@#@$$) d :: TyFun a Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

Methods

sing :: Sing ((>=@#@$$) d) #

(SOrd a, SingI d) => SingI ((<@#@$$) d :: TyFun a Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

Methods

sing :: Sing ((<@#@$$) d) #

(SOrd a, SingI d) => SingI ((<=@#@$$) d :: TyFun a Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

Methods

sing :: Sing ((<=@#@$$) d) #

SMonadPlus m => SingI (MfilterSym0 :: TyFun (a ~> Bool) (m a ~> m a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad

SApplicative m => SingI (FilterMSym0 :: TyFun (a ~> m Bool) ([a] ~> m [a]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad

SFoldable t => SingI (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing FindSym0 #

SFoldable t => SingI (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing AnySym0 #

SFoldable t => SingI (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing AllSym0 #

SuppressUnusedWarnings (Bool_Sym2 a6989586621679814557 a6989586621679814558 :: TyFun Bool a -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Bool

SuppressUnusedWarnings (Elem_bySym2 a6989586621680378588 a6989586621680378589 :: TyFun [a] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Lambda_6989586621681500761Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun Bool ([k1] ~> [k1]) -> Type) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad

SuppressUnusedWarnings (Let6989586621680378901Scrutinee_6989586621680375080Sym0 :: TyFun k1 (TyFun [a] (TyFun (k1 ~> Bool) (TyFun k Bool -> Type) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680378813Scrutinee_6989586621680375086Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680378800Scrutinee_6989586621680375088Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680378723Scrutinee_6989586621680375098Sym0 :: TyFun k1 (TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680378657Scrutinee_6989586621680375102Sym1 n6989586621680378655 :: TyFun k Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680378638Scrutinee_6989586621680375104Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680378625Scrutinee_6989586621680375106Sym0 :: TyFun k1 (TyFun k2 (TyFun [k1] (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680378609Scrutinee_6989586621680375108Sym0 :: TyFun k1 (TyFun k2 (TyFun [k1] (TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Null_6989586621680822324Sym0 :: TyFun (t a) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (NullSym0 :: TyFun (t a) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (NotElemSym1 a6989586621680821907 :: TyFun (t a) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Lambda_6989586621680822332Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680822360Sym1 a6989586621680822369 :: TyFun (t a) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (ElemSym1 a6989586621680822160 :: TyFun (t a) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (AnySym1 a6989586621680821965 :: TyFun (t a) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (AllSym1 a6989586621680821956 :: TyFun (t a) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (TFHelper_6989586621681202942Sym1 a6989586621681202947 :: TyFun (Arg a b) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

SuppressUnusedWarnings (TFHelper_6989586621680786553Sym1 a6989586621680786558 :: TyFun (Proxy s) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Proxy

SuppressUnusedWarnings (Lambda_6989586621681500758Sym0 :: TyFun (k2 ~> f Bool) (TyFun k3 (TyFun k2 (f [k2] ~> f [k2]) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad

SuppressUnusedWarnings (Lambda_6989586621681500596Sym0 :: TyFun (k1 ~> Bool) (TyFun k (TyFun k1 (m k1) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad

(SingI d1, SingI d2) => SingI (Bool_Sym2 d1 d2 :: TyFun Bool a -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Bool

Methods

sing :: Sing (Bool_Sym2 d1 d2) #

(SingI d1, SingI d2) => SingI (Elem_bySym2 d1 d2 :: TyFun [a] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (Elem_bySym2 d1 d2) #

SFoldable t => SingI (NullSym0 :: TyFun (t a) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing NullSym0 #

(SFoldable t, SEq a, SingI d) => SingI (NotElemSym1 d :: TyFun (t a) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (NotElemSym1 d) #

(SFoldable t, SEq a, SingI d) => SingI (ElemSym1 d :: TyFun (t a) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (ElemSym1 d) #

(SFoldable t, SingI d) => SingI (AnySym1 d :: TyFun (t a) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (AnySym1 d) #

(SFoldable t, SingI d) => SingI (AllSym1 d :: TyFun (t a) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (AllSym1 d) #

SuppressUnusedWarnings (Let6989586621680378901Scrutinee_6989586621680375080Sym1 x6989586621680378899 :: TyFun [a] (TyFun (k1 ~> Bool) (TyFun k Bool -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Lambda_6989586621681500761Sym1 x6989586621681500760 :: TyFun k2 (TyFun k3 (TyFun Bool ([k1] ~> [k1]) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad

SuppressUnusedWarnings (Let6989586621680378813Scrutinee_6989586621680375086Sym1 n6989586621680378810 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680378800Scrutinee_6989586621680375088Sym1 n6989586621680378797 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680378723Scrutinee_6989586621680375098Sym1 key6989586621680378719 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680378638Scrutinee_6989586621680375104Sym1 x6989586621680378635 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680378625Scrutinee_6989586621680375106Sym1 x6989586621680378622 :: TyFun k2 (TyFun [k1] (TyFun k3 Bool -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680378609Scrutinee_6989586621680375108Sym1 y6989586621680378606 :: TyFun k2 (TyFun [k1] (TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Lambda_6989586621680822332Sym1 a_69895866216808223266989586621680822331 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680180309Scrutinee_6989586621680180117Sym0 :: TyFun k1 (TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621680378625Scrutinee_6989586621680375106Sym2 x6989586621680378622 xs6989586621680378623 :: TyFun [k1] (TyFun k3 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680378609Scrutinee_6989586621680375108Sym2 y6989586621680378606 ys6989586621680378607 :: TyFun [k1] (TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Lambda_6989586621681500761Sym2 x6989586621681500760 p6989586621681500756 :: TyFun k3 (TyFun Bool ([k1] ~> [k1]) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad

SuppressUnusedWarnings (Let6989586621680378813Scrutinee_6989586621680375086Sym2 n6989586621680378810 x6989586621680378811 :: TyFun k3 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680378800Scrutinee_6989586621680375088Sym2 n6989586621680378797 x6989586621680378798 :: TyFun k3 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680378723Scrutinee_6989586621680375098Sym2 key6989586621680378719 x6989586621680378720 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680378638Scrutinee_6989586621680375104Sym2 x6989586621680378635 xs6989586621680378636 :: TyFun k3 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Lambda_6989586621680822332Sym2 a_69895866216808223266989586621680822331 arg_69895866216808217186989586621680822334 :: TyFun k3 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680180309Scrutinee_6989586621680180117Sym1 x6989586621680180308 :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621680180255Scrutinee_6989586621680180131Sym0 :: TyFun k1 (TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621680180218Scrutinee_6989586621680180141Sym0 :: TyFun k1 (TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621680378901Scrutinee_6989586621680375080Sym2 x6989586621680378899 xs6989586621680378900 :: TyFun (k1 ~> Bool) (TyFun k Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Lambda_6989586621680378950Sym0 :: TyFun (b ~> (a ~> Bool)) (TyFun k1 (TyFun k2 (TyFun a (TyFun [a] (TyFun b (m b) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Lambda_6989586621681500761Sym3 x6989586621681500760 p6989586621681500756 a_69895866216815007496989586621681500757 :: TyFun Bool ([k1] ~> [k1]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad

SuppressUnusedWarnings (Let6989586621680378901Scrutinee_6989586621680375080Sym3 x6989586621680378899 xs6989586621680378900 p6989586621680378895 :: TyFun k Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680378723Scrutinee_6989586621680375098Sym3 key6989586621680378719 x6989586621680378720 y6989586621680378721 :: TyFun k3 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680378625Scrutinee_6989586621680375106Sym3 x6989586621680378622 xs6989586621680378623 ls6989586621680378624 :: TyFun k3 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680180309Scrutinee_6989586621680180117Sym2 x6989586621680180308 x06989586621680180303 :: TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621680180255Scrutinee_6989586621680180131Sym1 x16989586621680180250 :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621680180218Scrutinee_6989586621680180141Sym1 x16989586621680180213 :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621680378609Scrutinee_6989586621680375108Sym3 y6989586621680378606 ys6989586621680378607 xs6989586621680378608 :: TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680378609Scrutinee_6989586621680375108Sym4 y6989586621680378606 ys6989586621680378607 xs6989586621680378608 eq6989586621680378600 :: TyFun k3 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680180309Scrutinee_6989586621680180117Sym3 x6989586621680180308 x06989586621680180303 y6989586621680180304 :: TyFun k3 (TyFun k4 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621680180255Scrutinee_6989586621680180131Sym2 x16989586621680180250 x26989586621680180251 :: TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621680180218Scrutinee_6989586621680180141Sym2 x16989586621680180213 x26989586621680180214 :: TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621680180309Scrutinee_6989586621680180117Sym4 x6989586621680180308 x06989586621680180303 y6989586621680180304 arg_69895866216801801136989586621680180299 :: TyFun k4 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621680180255Scrutinee_6989586621680180131Sym3 x16989586621680180250 x26989586621680180251 y6989586621680180252 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621680180218Scrutinee_6989586621680180141Sym3 x16989586621680180213 x26989586621680180214 y6989586621680180215 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621680180255Scrutinee_6989586621680180131Sym4 x16989586621680180250 x26989586621680180251 y6989586621680180252 arg_69895866216801801256989586621680180245 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621680180218Scrutinee_6989586621680180141Sym4 x16989586621680180213 x26989586621680180214 y6989586621680180215 arg_69895866216801801356989586621680180208 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621680180255Scrutinee_6989586621680180131Sym5 x16989586621680180250 x26989586621680180251 y6989586621680180252 arg_69895866216801801256989586621680180245 arg_69895866216801801276989586621680180246 :: TyFun k5 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621680180218Scrutinee_6989586621680180141Sym5 x16989586621680180213 x26989586621680180214 y6989586621680180215 arg_69895866216801801356989586621680180208 arg_69895866216801801376989586621680180209 :: TyFun k5 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Rep Bool 
Instance details

Defined in GHC.Generics

type Rep Bool = D1 ('MetaData "Bool" "GHC.Types" "ghc-prim" 'False) (C1 ('MetaCons "False" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "True" 'PrefixI 'False) (U1 :: Type -> Type))
newtype Vector Bool 
Instance details

Defined in Data.Vector.Unboxed.Base

type MaxBound 
Instance details

Defined in Data.Singletons.Prelude.Enum

type MaxBound = MaxBound_6989586621680176216Sym0
type MinBound 
Instance details

Defined in Data.Singletons.Prelude.Enum

type MinBound = MinBound_6989586621680176213Sym0
type Sing 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = SBool
type Demote Bool 
Instance details

Defined in Data.Singletons.Prelude.Instances

type DemoteRep Bool 
Instance details

Defined in GHC.Generics

type DemoteRep Bool = Bool
data Sing (a :: Bool) 
Instance details

Defined in GHC.Generics

data Sing (a :: Bool) where
type TypeDocFieldDescriptions Bool 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type ToT Bool 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT Bool = 'TBool
newtype MVector s Bool 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Bool = MV_Bool (MVector s Word8)
type Show_ (arg :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Show

type Show_ (arg :: Bool) = Apply (Show__6989586621680636125Sym0 :: TyFun Bool Symbol -> Type) arg
type FromEnum (a :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type FromEnum (a :: Bool) = Apply FromEnum_6989586621680203592Sym0 a
type ToEnum a 
Instance details

Defined in Data.Singletons.Prelude.Enum

type ToEnum a = Apply ToEnum_6989586621680203579Sym0 a
type Pred (arg :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Pred (arg :: Bool) = Apply (Pred_6989586621680180356Sym0 :: TyFun Bool Bool -> Type) arg
type Succ (arg :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Succ (arg :: Bool) = Apply (Succ_6989586621680180343Sym0 :: TyFun Bool Bool -> Type) arg
type UnaryArithResHs Not Bool Source # 
Instance details

Defined in Lorentz.Arith

type ShowList (arg1 :: [Bool]) arg2 
Instance details

Defined in Data.Singletons.Prelude.Show

type ShowList (arg1 :: [Bool]) arg2 = Apply (Apply (ShowList_6989586621680636133Sym0 :: TyFun [Bool] (Symbol ~> Symbol) -> Type) arg1) arg2
type EnumFromTo (arg1 :: Bool) (arg2 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type EnumFromTo (arg1 :: Bool) (arg2 :: Bool) = Apply (Apply (EnumFromTo_6989586621680180366Sym0 :: TyFun Bool (Bool ~> [Bool]) -> Type) arg1) arg2
type Min (arg1 :: Bool) (arg2 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Min (arg1 :: Bool) (arg2 :: Bool) = Apply (Apply (Min_6989586621679836854Sym0 :: TyFun Bool (Bool ~> Bool) -> Type) arg1) arg2
type Max (arg1 :: Bool) (arg2 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Max (arg1 :: Bool) (arg2 :: Bool) = Apply (Apply (Max_6989586621679836838Sym0 :: TyFun Bool (Bool ~> Bool) -> Type) arg1) arg2
type (arg1 :: Bool) >= (arg2 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type (arg1 :: Bool) >= (arg2 :: Bool) = Apply (Apply (TFHelper_6989586621679836822Sym0 :: TyFun Bool (Bool ~> Bool) -> Type) arg1) arg2
type (arg1 :: Bool) > (arg2 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type (arg1 :: Bool) > (arg2 :: Bool) = Apply (Apply (TFHelper_6989586621679836806Sym0 :: TyFun Bool (Bool ~> Bool) -> Type) arg1) arg2
type (arg1 :: Bool) <= (arg2 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type (arg1 :: Bool) <= (arg2 :: Bool) = Apply (Apply (TFHelper_6989586621679836790Sym0 :: TyFun Bool (Bool ~> Bool) -> Type) arg1) arg2
type (arg1 :: Bool) < (arg2 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type (arg1 :: Bool) < (arg2 :: Bool) = Apply (Apply (TFHelper_6989586621679836774Sym0 :: TyFun Bool (Bool ~> Bool) -> Type) arg1) arg2
type Compare (a1 :: Bool) (a2 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Compare (a1 :: Bool) (a2 :: Bool) = Apply (Apply Compare_6989586621679848336Sym0 a1) a2
type (x :: Bool) /= (y :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Eq

type (x :: Bool) /= (y :: Bool) = Not (x == y)
type (a :: Bool) == (b :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Eq

type (a :: Bool) == (b :: Bool) = Equals_6989586621679820016 a b
type ArithResHs And Bool Bool Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Or Bool Bool Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Xor Bool Bool Source # 
Instance details

Defined in Lorentz.Arith

type ShowsPrec a1 (a2 :: Bool) a3 
Instance details

Defined in Data.Singletons.Prelude.Show

type ShowsPrec a1 (a2 :: Bool) a3 = Apply (Apply (Apply ShowsPrec_6989586621680653401Sym0 a1) a2) a3
type EnumFromThenTo (arg1 :: Bool) (arg2 :: Bool) (arg3 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type EnumFromThenTo (arg1 :: Bool) (arg2 :: Bool) (arg3 :: Bool) = Apply (Apply (Apply (EnumFromThenTo_6989586621680180378Sym0 :: TyFun Bool (Bool ~> (Bool ~> [Bool])) -> Type) arg1) arg2) arg3
type Apply NotSym0 (a6989586621679815944 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Bool

type Apply NotSym0 (a6989586621679815944 :: Bool) = NotSym1 a6989586621679815944
type Apply FromEnum_6989586621680203592Sym0 (a6989586621680203596 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply FromEnum_6989586621680203592Sym0 (a6989586621680203596 :: Bool) = FromEnum_6989586621680203592Sym1 a6989586621680203596
type Apply All_Sym0 (a6989586621680362234 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal.Disambiguation

type Apply All_Sym0 (a6989586621680362234 :: Bool) = All_Sym1 a6989586621680362234
type Apply AllSym0 (a6989586621680249413 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply AllSym0 (a6989586621680249413 :: Bool) = AllSym1 a6989586621680249413
type Apply Any_Sym0 (a6989586621680362228 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal.Disambiguation

type Apply Any_Sym0 (a6989586621680362228 :: Bool) = Any_Sym1 a6989586621680362228
type Apply AnySym0 (a6989586621680249430 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply AnySym0 (a6989586621680249430 :: Bool) = AnySym1 a6989586621680249430
type Apply ToEnum_6989586621680203579Sym0 (a6989586621680203583 :: Nat) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply ToEnum_6989586621680203579Sym0 (a6989586621680203583 :: Nat) = ToEnum_6989586621680203579Sym1 a6989586621680203583
type Apply GetAllSym0 (a6989586621680249416 :: All) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply GetAllSym0 (a6989586621680249416 :: All) = GetAllSym1 a6989586621680249416
type Apply GetAnySym0 (a6989586621680249433 :: Any) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply GetAnySym0 (a6989586621680249433 :: Any) = GetAnySym1 a6989586621680249433
type Apply ((||@#@$$) a6989586621679815663 :: TyFun Bool Bool -> Type) (a6989586621679815664 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Bool

type Apply ((||@#@$$) a6989586621679815663 :: TyFun Bool Bool -> Type) (a6989586621679815664 :: Bool) = a6989586621679815663 ||@#@$$$ a6989586621679815664
type Apply ((&&@#@$$) a6989586621679815361 :: TyFun Bool Bool -> Type) (a6989586621679815362 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Bool

type Apply ((&&@#@$$) a6989586621679815361 :: TyFun Bool Bool -> Type) (a6989586621679815362 :: Bool) = a6989586621679815361 &&@#@$$$ a6989586621679815362
type Apply (Compare_6989586621679848336Sym1 a6989586621679848341 :: TyFun Bool Ordering -> Type) (a6989586621679848342 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Compare_6989586621679848336Sym1 a6989586621679848341 :: TyFun Bool Ordering -> Type) (a6989586621679848342 :: Bool) = Compare_6989586621679848336Sym2 a6989586621679848341 a6989586621679848342
type Apply ((<=?@#@$$) a6989586621679910080 :: TyFun Nat Bool -> Type) (a6989586621679910081 :: Nat) 
Instance details

Defined in Data.Singletons.TypeLits.Internal

type Apply ((<=?@#@$$) a6989586621679910080 :: TyFun Nat Bool -> Type) (a6989586621679910081 :: Nat) = a6989586621679910080 <=?@#@$$$ a6989586621679910081
type Apply (Let6989586621680786609Scrutinee_6989586621680786014Sym0 :: TyFun k1 Bool -> Type) (n6989586621680786608 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Proxy

type Apply (Let6989586621680786609Scrutinee_6989586621680786014Sym0 :: TyFun k1 Bool -> Type) (n6989586621680786608 :: k1) = Let6989586621680786609Scrutinee_6989586621680786014Sym1 n6989586621680786608
type Apply (Let6989586621680813445Scrutinee_6989586621680813409Sym1 x6989586621680813440 :: TyFun k1 Bool -> Type) (y6989586621680813441 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680813445Scrutinee_6989586621680813409Sym1 x6989586621680813440 :: TyFun k1 Bool -> Type) (y6989586621680813441 :: k1) = Let6989586621680813445Scrutinee_6989586621680813409Sym2 x6989586621680813440 y6989586621680813441
type Apply (Let6989586621680813469Scrutinee_6989586621680813411Sym1 x6989586621680813464 :: TyFun k1 Bool -> Type) (y6989586621680813465 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680813469Scrutinee_6989586621680813411Sym1 x6989586621680813464 :: TyFun k1 Bool -> Type) (y6989586621680813465 :: k1) = Let6989586621680813469Scrutinee_6989586621680813411Sym2 x6989586621680813464 y6989586621680813465
type Apply ((==@#@$$) a6989586621679818744 :: TyFun a Bool -> Type) (a6989586621679818745 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Eq

type Apply ((==@#@$$) a6989586621679818744 :: TyFun a Bool -> Type) (a6989586621679818745 :: a) = a6989586621679818744 ==@#@$$$ a6989586621679818745
type Apply ((/=@#@$$) a6989586621679818747 :: TyFun a Bool -> Type) (a6989586621679818748 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Eq

type Apply ((/=@#@$$) a6989586621679818747 :: TyFun a Bool -> Type) (a6989586621679818748 :: a) = a6989586621679818747 /=@#@$$$ a6989586621679818748
type Apply (DefaultEqSym1 a6989586621679818750 :: TyFun k Bool -> Type) (a6989586621679818751 :: k) 
Instance details

Defined in Data.Singletons.Prelude.Eq

type Apply (DefaultEqSym1 a6989586621679818750 :: TyFun k Bool -> Type) (a6989586621679818751 :: k) = DefaultEqSym2 a6989586621679818750 a6989586621679818751
type Apply (Let6989586621679836762Scrutinee_6989586621679836677Sym1 x6989586621679836760 :: TyFun k1 Bool -> Type) (y6989586621679836761 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Let6989586621679836762Scrutinee_6989586621679836677Sym1 x6989586621679836760 :: TyFun k1 Bool -> Type) (y6989586621679836761 :: k1) = Let6989586621679836762Scrutinee_6989586621679836677Sym2 x6989586621679836760 y6989586621679836761
type Apply (TFHelper_6989586621679836822Sym1 a6989586621679836827 :: TyFun a Bool -> Type) (a6989586621679836828 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (TFHelper_6989586621679836822Sym1 a6989586621679836827 :: TyFun a Bool -> Type) (a6989586621679836828 :: a) = TFHelper_6989586621679836822Sym2 a6989586621679836827 a6989586621679836828
type Apply (TFHelper_6989586621679836806Sym1 a6989586621679836811 :: TyFun a Bool -> Type) (a6989586621679836812 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (TFHelper_6989586621679836806Sym1 a6989586621679836811 :: TyFun a Bool -> Type) (a6989586621679836812 :: a) = TFHelper_6989586621679836806Sym2 a6989586621679836811 a6989586621679836812
type Apply (TFHelper_6989586621679836790Sym1 a6989586621679836795 :: TyFun a Bool -> Type) (a6989586621679836796 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (TFHelper_6989586621679836790Sym1 a6989586621679836795 :: TyFun a Bool -> Type) (a6989586621679836796 :: a) = TFHelper_6989586621679836790Sym2 a6989586621679836795 a6989586621679836796
type Apply (TFHelper_6989586621679836774Sym1 a6989586621679836779 :: TyFun a Bool -> Type) (a6989586621679836780 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (TFHelper_6989586621679836774Sym1 a6989586621679836779 :: TyFun a Bool -> Type) (a6989586621679836780 :: a) = TFHelper_6989586621679836774Sym2 a6989586621679836779 a6989586621679836780
type Apply ((<=@#@$$) a6989586621679836729 :: TyFun a Bool -> Type) (a6989586621679836730 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply ((<=@#@$$) a6989586621679836729 :: TyFun a Bool -> Type) (a6989586621679836730 :: a) = a6989586621679836729 <=@#@$$$ a6989586621679836730
type Apply ((>=@#@$$) a6989586621679836739 :: TyFun a Bool -> Type) (a6989586621679836740 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply ((>=@#@$$) a6989586621679836739 :: TyFun a Bool -> Type) (a6989586621679836740 :: a) = a6989586621679836739 >=@#@$$$ a6989586621679836740
type Apply ((>@#@$$) a6989586621679836734 :: TyFun a Bool -> Type) (a6989586621679836735 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply ((>@#@$$) a6989586621679836734 :: TyFun a Bool -> Type) (a6989586621679836735 :: a) = a6989586621679836734 >@#@$$$ a6989586621679836735
type Apply (Let6989586621679836863Scrutinee_6989586621679836691Sym1 x6989586621679836861 :: TyFun k1 Bool -> Type) (y6989586621679836862 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Let6989586621679836863Scrutinee_6989586621679836691Sym1 x6989586621679836861 :: TyFun k1 Bool -> Type) (y6989586621679836862 :: k1) = Let6989586621679836863Scrutinee_6989586621679836691Sym2 x6989586621679836861 y6989586621679836862
type Apply (Let6989586621679836847Scrutinee_6989586621679836689Sym1 x6989586621679836845 :: TyFun k1 Bool -> Type) (y6989586621679836846 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Let6989586621679836847Scrutinee_6989586621679836689Sym1 x6989586621679836845 :: TyFun k1 Bool -> Type) (y6989586621679836846 :: k1) = Let6989586621679836847Scrutinee_6989586621679836689Sym2 x6989586621679836845 y6989586621679836846
type Apply (Let6989586621679836766Scrutinee_6989586621679836679Sym1 x6989586621679836760 :: TyFun k1 Bool -> Type) (y6989586621679836761 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Let6989586621679836766Scrutinee_6989586621679836679Sym1 x6989586621679836760 :: TyFun k1 Bool -> Type) (y6989586621679836761 :: k1) = Let6989586621679836766Scrutinee_6989586621679836679Sym2 x6989586621679836760 y6989586621679836761
type Apply ((<@#@$$) a6989586621679836724 :: TyFun a Bool -> Type) (a6989586621679836725 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply ((<@#@$$) a6989586621679836724 :: TyFun a Bool -> Type) (a6989586621679836725 :: a) = a6989586621679836724 <@#@$$$ a6989586621679836725
type Apply (Bool_Sym2 a6989586621679814557 a6989586621679814558 :: TyFun Bool a -> Type) (a6989586621679814559 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Bool

type Apply (Bool_Sym2 a6989586621679814557 a6989586621679814558 :: TyFun Bool a -> Type) (a6989586621679814559 :: Bool) = Bool_Sym3 a6989586621679814557 a6989586621679814558 a6989586621679814559
type Apply (Let6989586621680378657Scrutinee_6989586621680375102Sym1 n6989586621680378655 :: TyFun k Bool -> Type) (x6989586621680378656 :: k) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680378657Scrutinee_6989586621680375102Sym1 n6989586621680378655 :: TyFun k Bool -> Type) (x6989586621680378656 :: k) = Let6989586621680378657Scrutinee_6989586621680375102Sym2 n6989586621680378655 x6989586621680378656
type Apply (Let6989586621680378638Scrutinee_6989586621680375104Sym2 x6989586621680378635 xs6989586621680378636 :: TyFun k3 Bool -> Type) (n6989586621680378637 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680378638Scrutinee_6989586621680375104Sym2 x6989586621680378635 xs6989586621680378636 :: TyFun k3 Bool -> Type) (n6989586621680378637 :: k3) = Let6989586621680378638Scrutinee_6989586621680375104Sym3 x6989586621680378635 xs6989586621680378636 n6989586621680378637
type Apply (Let6989586621680378800Scrutinee_6989586621680375088Sym2 n6989586621680378797 x6989586621680378798 :: TyFun k3 Bool -> Type) (xs6989586621680378799 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680378800Scrutinee_6989586621680375088Sym2 n6989586621680378797 x6989586621680378798 :: TyFun k3 Bool -> Type) (xs6989586621680378799 :: k3) = Let6989586621680378800Scrutinee_6989586621680375088Sym3 n6989586621680378797 x6989586621680378798 xs6989586621680378799
type Apply (Let6989586621680378813Scrutinee_6989586621680375086Sym2 n6989586621680378810 x6989586621680378811 :: TyFun k3 Bool -> Type) (xs6989586621680378812 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680378813Scrutinee_6989586621680375086Sym2 n6989586621680378810 x6989586621680378811 :: TyFun k3 Bool -> Type) (xs6989586621680378812 :: k3) = Let6989586621680378813Scrutinee_6989586621680375086Sym3 n6989586621680378810 x6989586621680378811 xs6989586621680378812
type Apply (Lambda_6989586621680822332Sym2 a_69895866216808223266989586621680822331 arg_69895866216808217186989586621680822334 :: TyFun k3 Bool -> Type) (arg_69895866216808217206989586621680822335 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Lambda_6989586621680822332Sym2 a_69895866216808223266989586621680822331 arg_69895866216808217186989586621680822334 :: TyFun k3 Bool -> Type) (arg_69895866216808217206989586621680822335 :: k3) = Lambda_6989586621680822332Sym3 a_69895866216808223266989586621680822331 arg_69895866216808217186989586621680822334 arg_69895866216808217206989586621680822335
type Apply (Let6989586621680378723Scrutinee_6989586621680375098Sym3 key6989586621680378719 x6989586621680378720 y6989586621680378721 :: TyFun k3 Bool -> Type) (xys6989586621680378722 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680378723Scrutinee_6989586621680375098Sym3 key6989586621680378719 x6989586621680378720 y6989586621680378721 :: TyFun k3 Bool -> Type) (xys6989586621680378722 :: k3) = Let6989586621680378723Scrutinee_6989586621680375098Sym4 key6989586621680378719 x6989586621680378720 y6989586621680378721 xys6989586621680378722
type Apply (Let6989586621680378625Scrutinee_6989586621680375106Sym3 x6989586621680378622 xs6989586621680378623 ls6989586621680378624 :: TyFun k3 Bool -> Type) (l6989586621680378617 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680378625Scrutinee_6989586621680375106Sym3 x6989586621680378622 xs6989586621680378623 ls6989586621680378624 :: TyFun k3 Bool -> Type) (l6989586621680378617 :: k3) = Let6989586621680378625Scrutinee_6989586621680375106Sym4 x6989586621680378622 xs6989586621680378623 ls6989586621680378624 l6989586621680378617
type Apply (Let6989586621680378901Scrutinee_6989586621680375080Sym3 x6989586621680378899 xs6989586621680378900 p6989586621680378895 :: TyFun k Bool -> Type) (a_69895866216803788886989586621680378896 :: k) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680378901Scrutinee_6989586621680375080Sym3 x6989586621680378899 xs6989586621680378900 p6989586621680378895 :: TyFun k Bool -> Type) (a_69895866216803788886989586621680378896 :: k) = Let6989586621680378901Scrutinee_6989586621680375080Sym4 x6989586621680378899 xs6989586621680378900 p6989586621680378895 a_69895866216803788886989586621680378896
type Apply (Let6989586621680378609Scrutinee_6989586621680375108Sym4 y6989586621680378606 ys6989586621680378607 xs6989586621680378608 eq6989586621680378600 :: TyFun k3 Bool -> Type) (l6989586621680378601 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680378609Scrutinee_6989586621680375108Sym4 y6989586621680378606 ys6989586621680378607 xs6989586621680378608 eq6989586621680378600 :: TyFun k3 Bool -> Type) (l6989586621680378601 :: k3) = Let6989586621680378609Scrutinee_6989586621680375108Sym5 y6989586621680378606 ys6989586621680378607 xs6989586621680378608 eq6989586621680378600 l6989586621680378601
type Apply (Let6989586621680180309Scrutinee_6989586621680180117Sym4 x6989586621680180308 x06989586621680180303 y6989586621680180304 arg_69895866216801801136989586621680180299 :: TyFun k4 Bool -> Type) (arg_69895866216801801156989586621680180300 :: k4) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621680180309Scrutinee_6989586621680180117Sym4 x6989586621680180308 x06989586621680180303 y6989586621680180304 arg_69895866216801801136989586621680180299 :: TyFun k4 Bool -> Type) (arg_69895866216801801156989586621680180300 :: k4) = Let6989586621680180309Scrutinee_6989586621680180117Sym5 x6989586621680180308 x06989586621680180303 y6989586621680180304 arg_69895866216801801136989586621680180299 arg_69895866216801801156989586621680180300
type Apply (Let6989586621680180218Scrutinee_6989586621680180141Sym5 x16989586621680180213 x26989586621680180214 y6989586621680180215 arg_69895866216801801356989586621680180208 arg_69895866216801801376989586621680180209 :: TyFun k5 Bool -> Type) (arg_69895866216801801396989586621680180210 :: k5) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621680180218Scrutinee_6989586621680180141Sym5 x16989586621680180213 x26989586621680180214 y6989586621680180215 arg_69895866216801801356989586621680180208 arg_69895866216801801376989586621680180209 :: TyFun k5 Bool -> Type) (arg_69895866216801801396989586621680180210 :: k5) = Let6989586621680180218Scrutinee_6989586621680180141Sym6 x16989586621680180213 x26989586621680180214 y6989586621680180215 arg_69895866216801801356989586621680180208 arg_69895866216801801376989586621680180209 arg_69895866216801801396989586621680180210
type Apply (Let6989586621680180255Scrutinee_6989586621680180131Sym5 x16989586621680180250 x26989586621680180251 y6989586621680180252 arg_69895866216801801256989586621680180245 arg_69895866216801801276989586621680180246 :: TyFun k5 Bool -> Type) (arg_69895866216801801296989586621680180247 :: k5) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621680180255Scrutinee_6989586621680180131Sym5 x16989586621680180250 x26989586621680180251 y6989586621680180252 arg_69895866216801801256989586621680180245 arg_69895866216801801276989586621680180246 :: TyFun k5 Bool -> Type) (arg_69895866216801801296989586621680180247 :: k5) = Let6989586621680180255Scrutinee_6989586621680180131Sym6 x16989586621680180250 x26989586621680180251 y6989586621680180252 arg_69895866216801801256989586621680180245 arg_69895866216801801276989586621680180246 arg_69895866216801801296989586621680180247
type Eval (Not 'False) 
Instance details

Defined in Fcf.Data.Bool

type Eval (Not 'False) = 'True
type Eval (Not 'True) 
Instance details

Defined in Fcf.Data.Bool

type Eval (Not 'True) = 'False
type Apply (GuardSym0 :: TyFun Bool (f ()) -> Type) (a6989586621680011056 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (GuardSym0 :: TyFun Bool (f ()) -> Type) (a6989586621680011056 :: Bool) = GuardSym1 a6989586621680011056 :: f ()
type Eval (Null (a2 ': as) :: Bool -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (Null (a2 ': as) :: Bool -> Type) = 'False
type Eval (Null ('[] :: [a]) :: Bool -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (Null ('[] :: [a]) :: Bool -> Type) = 'True
type Eval (And lst :: Bool -> Type) 
Instance details

Defined in Fcf.Class.Foldable

type Eval (And lst :: Bool -> Type) = Eval (Foldr (&&) 'True lst)
type Eval (Or lst :: Bool -> Type) 
Instance details

Defined in Fcf.Class.Foldable

type Eval (Or lst :: Bool -> Type) = Eval (Foldr (||) 'False lst)
type Eval (a <= b :: Bool -> Type) 
Instance details

Defined in Fcf.Data.Nat

type Eval (a <= b :: Bool -> Type) = a <=? b
type Eval (a >= b :: Bool -> Type) 
Instance details

Defined in Fcf.Data.Nat

type Eval (a >= b :: Bool -> Type) = b <=? a
type Eval (a < b :: Bool -> Type) 
Instance details

Defined in Fcf.Data.Nat

type Eval (a < b :: Bool -> Type) = Eval (Not =<< (a >= b))
type Eval (a > b :: Bool -> Type) 
Instance details

Defined in Fcf.Data.Nat

type Eval (a > b :: Bool -> Type) = Eval (Not =<< (a <= b))
type Eval (IsNothing ('Nothing :: Maybe a) :: Bool -> Type) 
Instance details

Defined in Fcf.Data.Common

type Eval (IsNothing ('Nothing :: Maybe a) :: Bool -> Type) = 'True
type Eval (IsNothing ('Just _a) :: Bool -> Type) 
Instance details

Defined in Fcf.Data.Common

type Eval (IsNothing ('Just _a) :: Bool -> Type) = 'False
type Eval (IsJust ('Nothing :: Maybe a) :: Bool -> Type) 
Instance details

Defined in Fcf.Data.Common

type Eval (IsJust ('Nothing :: Maybe a) :: Bool -> Type) = 'False
type Eval (IsJust ('Just _a) :: Bool -> Type) 
Instance details

Defined in Fcf.Data.Common

type Eval (IsJust ('Just _a) :: Bool -> Type) = 'True
type Eval ('False || b :: Bool -> Type) 
Instance details

Defined in Fcf.Data.Bool

type Eval ('False || b :: Bool -> Type) = b
type Eval ('True || b :: Bool -> Type) 
Instance details

Defined in Fcf.Data.Bool

type Eval ('True || b :: Bool -> Type) = 'True
type Eval (a || 'False :: Bool -> Type) 
Instance details

Defined in Fcf.Data.Bool

type Eval (a || 'False :: Bool -> Type) = a
type Eval (a || 'True :: Bool -> Type) 
Instance details

Defined in Fcf.Data.Bool

type Eval (a || 'True :: Bool -> Type) = 'True
type Eval ('False && b :: Bool -> Type) 
Instance details

Defined in Fcf.Data.Bool

type Eval ('False && b :: Bool -> Type) = 'False
type Eval ('True && b :: Bool -> Type) 
Instance details

Defined in Fcf.Data.Bool

type Eval ('True && b :: Bool -> Type) = b
type Eval (a && 'True :: Bool -> Type) 
Instance details

Defined in Fcf.Data.Bool

type Eval (a && 'True :: Bool -> Type) = a
type Eval (a && 'False :: Bool -> Type) 
Instance details

Defined in Fcf.Data.Bool

type Eval (a && 'False :: Bool -> Type) = 'False
type Apply (||@#@$) (a6989586621679815663 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Bool

type Apply (||@#@$) (a6989586621679815663 :: Bool) = (||@#@$$) a6989586621679815663
type Apply (&&@#@$) (a6989586621679815361 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Bool

type Apply (&&@#@$) (a6989586621679815361 :: Bool) = (&&@#@$$) a6989586621679815361
type Apply Compare_6989586621679848336Sym0 (a6989586621679848341 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply Compare_6989586621679848336Sym0 (a6989586621679848341 :: Bool) = Compare_6989586621679848336Sym1 a6989586621679848341
type Apply ShowParenSym0 (a6989586621680636038 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply ShowParenSym0 (a6989586621680636038 :: Bool) = ShowParenSym1 a6989586621680636038
type Apply ShowsPrec_6989586621680653401Sym0 (a6989586621680653411 :: Nat) 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply ShowsPrec_6989586621680653401Sym0 (a6989586621680653411 :: Nat) = ShowsPrec_6989586621680653401Sym1 a6989586621680653411
type Apply (<=?@#@$) (a6989586621679910080 :: Nat) 
Instance details

Defined in Data.Singletons.TypeLits.Internal

type Apply (<=?@#@$) (a6989586621679910080 :: Nat) = (<=?@#@$$) a6989586621679910080
type Apply (ShowsPrec_6989586621680653401Sym1 a6989586621680653411 :: TyFun Bool (Symbol ~> Symbol) -> Type) (a6989586621680653412 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowsPrec_6989586621680653401Sym1 a6989586621680653411 :: TyFun Bool (Symbol ~> Symbol) -> Type) (a6989586621680653412 :: Bool) = ShowsPrec_6989586621680653401Sym2 a6989586621680653411 a6989586621680653412
type Apply (UnlessSym0 :: TyFun Bool (f () ~> f ()) -> Type) (a6989586621681500621 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Monad

type Apply (UnlessSym0 :: TyFun Bool (f () ~> f ()) -> Type) (a6989586621681500621 :: Bool) = UnlessSym1 a6989586621681500621 :: TyFun (f ()) (f ()) -> Type
type Apply (WhenSym0 :: TyFun Bool (f () ~> f ()) -> Type) (a6989586621680011200 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (WhenSym0 :: TyFun Bool (f () ~> f ()) -> Type) (a6989586621680011200 :: Bool) = WhenSym1 a6989586621680011200 :: TyFun (f ()) (f ()) -> Type
type Apply (ListelemSym0 :: TyFun a ([a] ~> Bool) -> Type) (a6989586621680748782 :: a) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal.Disambiguation

type Apply (ListelemSym0 :: TyFun a ([a] ~> Bool) -> Type) (a6989586621680748782 :: a) = ListelemSym1 a6989586621680748782
type Apply (NotElemSym0 :: TyFun a ([a] ~> Bool) -> Type) (a6989586621680379352 :: a) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (NotElemSym0 :: TyFun a ([a] ~> Bool) -> Type) (a6989586621680379352 :: a) = NotElemSym1 a6989586621680379352
type Apply (ElemSym0 :: TyFun a ([a] ~> Bool) -> Type) (a6989586621680379360 :: a) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ElemSym0 :: TyFun a ([a] ~> Bool) -> Type) (a6989586621680379360 :: a) = ElemSym1 a6989586621680379360
type Apply (Let6989586621680813445Scrutinee_6989586621680813409Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621680813440 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680813445Scrutinee_6989586621680813409Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621680813440 :: k1) = Let6989586621680813445Scrutinee_6989586621680813409Sym1 x6989586621680813440
type Apply (Let6989586621680813469Scrutinee_6989586621680813411Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621680813464 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680813469Scrutinee_6989586621680813411Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621680813464 :: k1) = Let6989586621680813469Scrutinee_6989586621680813411Sym1 x6989586621680813464
type Apply (Elem_6989586621680822470Sym0 :: TyFun a ([a] ~> Bool) -> Type) (a6989586621680822479 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680822470Sym0 :: TyFun a ([a] ~> Bool) -> Type) (a6989586621680822479 :: a) = Elem_6989586621680822470Sym1 a6989586621680822479
type Apply (Elem_6989586621680822846Sym0 :: TyFun a (Proxy a ~> Bool) -> Type) (a6989586621680822851 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680822846Sym0 :: TyFun a (Proxy a ~> Bool) -> Type) (a6989586621680822851 :: a) = Elem_6989586621680822846Sym1 a6989586621680822851
type Apply (Elem_6989586621680822878Sym0 :: TyFun a (Dual a ~> Bool) -> Type) (a6989586621680822887 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680822878Sym0 :: TyFun a (Dual a ~> Bool) -> Type) (a6989586621680822887 :: a) = Elem_6989586621680822878Sym1 a6989586621680822887
type Apply (Elem_6989586621680823053Sym0 :: TyFun a (Sum a ~> Bool) -> Type) (a6989586621680823062 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680823053Sym0 :: TyFun a (Sum a ~> Bool) -> Type) (a6989586621680823062 :: a) = Elem_6989586621680823053Sym1 a6989586621680823062
type Apply (Elem_6989586621680823228Sym0 :: TyFun a (Product a ~> Bool) -> Type) (a6989586621680823237 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680823228Sym0 :: TyFun a (Product a ~> Bool) -> Type) (a6989586621680823237 :: a) = Elem_6989586621680823228Sym1 a6989586621680823237
type Apply ((==@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679818744 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Eq

type Apply ((==@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679818744 :: a) = (==@#@$$) a6989586621679818744
type Apply ((/=@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679818747 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Eq

type Apply ((/=@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679818747 :: a) = (/=@#@$$) a6989586621679818747
type Apply (DefaultEqSym0 :: TyFun k (k ~> Bool) -> Type) (a6989586621679818750 :: k) 
Instance details

Defined in Data.Singletons.Prelude.Eq

type Apply (DefaultEqSym0 :: TyFun k (k ~> Bool) -> Type) (a6989586621679818750 :: k) = DefaultEqSym1 a6989586621679818750
type Apply (Bool_Sym0 :: TyFun a (a ~> (Bool ~> a)) -> Type) (a6989586621679814557 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Bool

type Apply (Bool_Sym0 :: TyFun a (a ~> (Bool ~> a)) -> Type) (a6989586621679814557 :: a) = Bool_Sym1 a6989586621679814557
type Apply (Let6989586621679836762Scrutinee_6989586621679836677Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679836760 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Let6989586621679836762Scrutinee_6989586621679836677Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679836760 :: k1) = Let6989586621679836762Scrutinee_6989586621679836677Sym1 x6989586621679836760
type Apply (TFHelper_6989586621679836822Sym0 :: TyFun a (a ~> Bool) -> Type) (a6989586621679836827 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (TFHelper_6989586621679836822Sym0 :: TyFun a (a ~> Bool) -> Type) (a6989586621679836827 :: a) = TFHelper_6989586621679836822Sym1 a6989586621679836827
type Apply (TFHelper_6989586621679836806Sym0 :: TyFun a (a ~> Bool) -> Type) (a6989586621679836811 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (TFHelper_6989586621679836806Sym0 :: TyFun a (a ~> Bool) -> Type) (a6989586621679836811 :: a) = TFHelper_6989586621679836806Sym1 a6989586621679836811
type Apply (TFHelper_6989586621679836790Sym0 :: TyFun a (a ~> Bool) -> Type) (a6989586621679836795 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (TFHelper_6989586621679836790Sym0 :: TyFun a (a ~> Bool) -> Type) (a6989586621679836795 :: a) = TFHelper_6989586621679836790Sym1 a6989586621679836795
type Apply (TFHelper_6989586621679836774Sym0 :: TyFun a (a ~> Bool) -> Type) (a6989586621679836779 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (TFHelper_6989586621679836774Sym0 :: TyFun a (a ~> Bool) -> Type) (a6989586621679836779 :: a) = TFHelper_6989586621679836774Sym1 a6989586621679836779
type Apply ((<=@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679836729 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply ((<=@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679836729 :: a) = (<=@#@$$) a6989586621679836729
type Apply ((>=@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679836739 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply ((>=@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679836739 :: a) = (>=@#@$$) a6989586621679836739
type Apply ((>@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679836734 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply ((>@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679836734 :: a) = (>@#@$$) a6989586621679836734
type Apply (Let6989586621679836863Scrutinee_6989586621679836691Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679836861 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Let6989586621679836863Scrutinee_6989586621679836691Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679836861 :: k1) = Let6989586621679836863Scrutinee_6989586621679836691Sym1 x6989586621679836861
type Apply (Let6989586621679836847Scrutinee_6989586621679836689Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679836845 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Let6989586621679836847Scrutinee_6989586621679836689Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679836845 :: k1) = Let6989586621679836847Scrutinee_6989586621679836689Sym1 x6989586621679836845
type Apply (Let6989586621679836766Scrutinee_6989586621679836679Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679836760 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Let6989586621679836766Scrutinee_6989586621679836679Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679836760 :: k1) = Let6989586621679836766Scrutinee_6989586621679836679Sym1 x6989586621679836760
type Apply ((<@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679836724 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply ((<@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679836724 :: a) = (<@#@$$) a6989586621679836724
type Apply (Elem_6989586621681011897Sym0 :: TyFun a (Identity a ~> Bool) -> Type) (a6989586621681011902 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Identity

type Apply (Elem_6989586621681011897Sym0 :: TyFun a (Identity a ~> Bool) -> Type) (a6989586621681011902 :: a) = Elem_6989586621681011897Sym1 a6989586621681011902
type Apply (Let6989586621680378657Scrutinee_6989586621680375102Sym0 :: TyFun k1 (TyFun k Bool -> Type) -> Type) (n6989586621680378655 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680378657Scrutinee_6989586621680375102Sym0 :: TyFun k1 (TyFun k Bool -> Type) -> Type) (n6989586621680378655 :: k1) = Let6989586621680378657Scrutinee_6989586621680375102Sym1 n6989586621680378655 :: TyFun k Bool -> Type
type Apply (Elem_bySym1 a6989586621680378588 :: TyFun a ([a] ~> Bool) -> Type) (a6989586621680378589 :: a) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Elem_bySym1 a6989586621680378588 :: TyFun a ([a] ~> Bool) -> Type) (a6989586621680378589 :: a) = Elem_bySym2 a6989586621680378588 a6989586621680378589
type Apply (Elem_6989586621680822360Sym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621680822369 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680822360Sym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621680822369 :: a) = Elem_6989586621680822360Sym1 a6989586621680822369 :: TyFun (t a) Bool -> Type
type Apply (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621680822160 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621680822160 :: a) = ElemSym1 a6989586621680822160 :: TyFun (t a) Bool -> Type
type Apply (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621680821907 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621680821907 :: a) = NotElemSym1 a6989586621680821907 :: TyFun (t a) Bool -> Type
type Apply (Bool_Sym1 a6989586621679814557 :: TyFun a (Bool ~> a) -> Type) (a6989586621679814558 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Bool

type Apply (Bool_Sym1 a6989586621679814557 :: TyFun a (Bool ~> a) -> Type) (a6989586621679814558 :: a) = Bool_Sym2 a6989586621679814557 a6989586621679814558
type Apply (Lambda_6989586621681500761Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun Bool ([k1] ~> [k1]) -> Type) -> Type) -> Type) -> Type) (x6989586621681500760 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Monad

type Apply (Lambda_6989586621681500761Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun Bool ([k1] ~> [k1]) -> Type) -> Type) -> Type) -> Type) (x6989586621681500760 :: k1) = Lambda_6989586621681500761Sym1 x6989586621681500760 :: TyFun k2 (TyFun k3 (TyFun Bool ([k1] ~> [k1]) -> Type) -> Type) -> Type
type Apply (Let6989586621680378638Scrutinee_6989586621680375104Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (x6989586621680378635 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680378638Scrutinee_6989586621680375104Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (x6989586621680378635 :: k1) = Let6989586621680378638Scrutinee_6989586621680375104Sym1 x6989586621680378635 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type
type Apply (Let6989586621680378723Scrutinee_6989586621680375098Sym0 :: TyFun k1 (TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) (key6989586621680378719 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680378723Scrutinee_6989586621680375098Sym0 :: TyFun k1 (TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) (key6989586621680378719 :: k1) = Let6989586621680378723Scrutinee_6989586621680375098Sym1 key6989586621680378719 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type
type Apply (Let6989586621680378800Scrutinee_6989586621680375088Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (n6989586621680378797 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680378800Scrutinee_6989586621680375088Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (n6989586621680378797 :: k1) = Let6989586621680378800Scrutinee_6989586621680375088Sym1 n6989586621680378797 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type
type Apply (Let6989586621680378813Scrutinee_6989586621680375086Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (n6989586621680378810 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680378813Scrutinee_6989586621680375086Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (n6989586621680378810 :: k1) = Let6989586621680378813Scrutinee_6989586621680375086Sym1 n6989586621680378810 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type
type Apply (Let6989586621680378609Scrutinee_6989586621680375108Sym0 :: TyFun k1 (TyFun k2 (TyFun [k1] (TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (y6989586621680378606 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680378609Scrutinee_6989586621680375108Sym0 :: TyFun k1 (TyFun k2 (TyFun [k1] (TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (y6989586621680378606 :: k1) = Let6989586621680378609Scrutinee_6989586621680375108Sym1 y6989586621680378606 :: TyFun k2 (TyFun [k1] (TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621680378625Scrutinee_6989586621680375106Sym0 :: TyFun k1 (TyFun k2 (TyFun [k1] (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) (x6989586621680378622 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680378625Scrutinee_6989586621680375106Sym0 :: TyFun k1 (TyFun k2 (TyFun [k1] (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) (x6989586621680378622 :: k1) = Let6989586621680378625Scrutinee_6989586621680375106Sym1 x6989586621680378622 :: TyFun k2 (TyFun [k1] (TyFun k3 Bool -> Type) -> Type) -> Type
type Apply (Let6989586621680378901Scrutinee_6989586621680375080Sym0 :: TyFun k1 (TyFun [a] (TyFun (k1 ~> Bool) (TyFun k Bool -> Type) -> Type) -> Type) -> Type) (x6989586621680378899 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680378901Scrutinee_6989586621680375080Sym0 :: TyFun k1 (TyFun [a] (TyFun (k1 ~> Bool) (TyFun k Bool -> Type) -> Type) -> Type) -> Type) (x6989586621680378899 :: k1) = Let6989586621680378901Scrutinee_6989586621680375080Sym1 x6989586621680378899 :: TyFun [a] (TyFun (k1 ~> Bool) (TyFun k Bool -> Type) -> Type) -> Type
type Apply (Lambda_6989586621680822332Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (a_69895866216808223266989586621680822331 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Lambda_6989586621680822332Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (a_69895866216808223266989586621680822331 :: k1) = Lambda_6989586621680822332Sym1 a_69895866216808223266989586621680822331 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type
type Apply (Lambda_6989586621681500761Sym1 x6989586621681500760 :: TyFun k2 (TyFun k3 (TyFun Bool ([k1] ~> [k1]) -> Type) -> Type) -> Type) (p6989586621681500756 :: k2) 
Instance details

Defined in Data.Singletons.Prelude.Monad

type Apply (Lambda_6989586621681500761Sym1 x6989586621681500760 :: TyFun k2 (TyFun k3 (TyFun Bool ([k1] ~> [k1]) -> Type) -> Type) -> Type) (p6989586621681500756 :: k2) = Lambda_6989586621681500761Sym2 x6989586621681500760 p6989586621681500756 :: TyFun k3 (TyFun Bool ([k1] ~> [k1]) -> Type) -> Type
type Apply (Let6989586621680378638Scrutinee_6989586621680375104Sym1 x6989586621680378635 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) (xs6989586621680378636 :: k2) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680378638Scrutinee_6989586621680375104Sym1 x6989586621680378635 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) (xs6989586621680378636 :: k2) = Let6989586621680378638Scrutinee_6989586621680375104Sym2 x6989586621680378635 xs6989586621680378636 :: TyFun k3 Bool -> Type
type Apply (Let6989586621680378723Scrutinee_6989586621680375098Sym1 key6989586621680378719 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (x6989586621680378720 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680378723Scrutinee_6989586621680375098Sym1 key6989586621680378719 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (x6989586621680378720 :: k1) = Let6989586621680378723Scrutinee_6989586621680375098Sym2 key6989586621680378719 x6989586621680378720 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type
type Apply (Let6989586621680378800Scrutinee_6989586621680375088Sym1 n6989586621680378797 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) (x6989586621680378798 :: k2) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680378800Scrutinee_6989586621680375088Sym1 n6989586621680378797 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) (x6989586621680378798 :: k2) = Let6989586621680378800Scrutinee_6989586621680375088Sym2 n6989586621680378797 x6989586621680378798 :: TyFun k3 Bool -> Type
type Apply (Let6989586621680378813Scrutinee_6989586621680375086Sym1 n6989586621680378810 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) (x6989586621680378811 :: k2) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680378813Scrutinee_6989586621680375086Sym1 n6989586621680378810 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) (x6989586621680378811 :: k2) = Let6989586621680378813Scrutinee_6989586621680375086Sym2 n6989586621680378810 x6989586621680378811 :: TyFun k3 Bool -> Type
type Apply (Let6989586621680378609Scrutinee_6989586621680375108Sym1 y6989586621680378606 :: TyFun k2 (TyFun [k1] (TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) (ys6989586621680378607 :: k2) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680378609Scrutinee_6989586621680375108Sym1 y6989586621680378606 :: TyFun k2 (TyFun [k1] (TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) (ys6989586621680378607 :: k2) = Let6989586621680378609Scrutinee_6989586621680375108Sym2 y6989586621680378606 ys6989586621680378607 :: TyFun [k1] (TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type) -> Type
type Apply (Let6989586621680378625Scrutinee_6989586621680375106Sym1 x6989586621680378622 :: TyFun k2 (TyFun [k1] (TyFun k3 Bool -> Type) -> Type) -> Type) (xs6989586621680378623 :: k2) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680378625Scrutinee_6989586621680375106Sym1 x6989586621680378622 :: TyFun k2 (TyFun [k1] (TyFun k3 Bool -> Type) -> Type) -> Type) (xs6989586621680378623 :: k2) = Let6989586621680378625Scrutinee_6989586621680375106Sym2 x6989586621680378622 xs6989586621680378623 :: TyFun [k1] (TyFun k3 Bool -> Type) -> Type
type Apply (Lambda_6989586621680822332Sym1 a_69895866216808223266989586621680822331 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) (arg_69895866216808217186989586621680822334 :: k2) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Lambda_6989586621680822332Sym1 a_69895866216808223266989586621680822331 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) (arg_69895866216808217186989586621680822334 :: k2) = Lambda_6989586621680822332Sym2 a_69895866216808223266989586621680822331 arg_69895866216808217186989586621680822334 :: TyFun k3 Bool -> Type
type Apply (Let6989586621680180309Scrutinee_6989586621680180117Sym0 :: TyFun k1 (TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (x6989586621680180308 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621680180309Scrutinee_6989586621680180117Sym0 :: TyFun k1 (TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (x6989586621680180308 :: k1) = Let6989586621680180309Scrutinee_6989586621680180117Sym1 x6989586621680180308 :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621681500761Sym2 x6989586621681500760 p6989586621681500756 :: TyFun k3 (TyFun Bool ([k1] ~> [k1]) -> Type) -> Type) (a_69895866216815007496989586621681500757 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.Monad

type Apply (Lambda_6989586621681500761Sym2 x6989586621681500760 p6989586621681500756 :: TyFun k3 (TyFun Bool ([k1] ~> [k1]) -> Type) -> Type) (a_69895866216815007496989586621681500757 :: k3) = Lambda_6989586621681500761Sym3 x6989586621681500760 p6989586621681500756 a_69895866216815007496989586621681500757
type Apply (Let6989586621680378723Scrutinee_6989586621680375098Sym2 key6989586621680378719 x6989586621680378720 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) (y6989586621680378721 :: k2) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680378723Scrutinee_6989586621680375098Sym2 key6989586621680378719 x6989586621680378720 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) (y6989586621680378721 :: k2) = Let6989586621680378723Scrutinee_6989586621680375098Sym3 key6989586621680378719 x6989586621680378720 y6989586621680378721 :: TyFun k3 Bool -> Type
type Apply (Let6989586621680180218Scrutinee_6989586621680180141Sym0 :: TyFun k1 (TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (x16989586621680180213 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621680180218Scrutinee_6989586621680180141Sym0 :: TyFun k1 (TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (x16989586621680180213 :: k1) = Let6989586621680180218Scrutinee_6989586621680180141Sym1 x16989586621680180213 :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621680180255Scrutinee_6989586621680180131Sym0 :: TyFun k1 (TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (x16989586621680180250 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621680180255Scrutinee_6989586621680180131Sym0 :: TyFun k1 (TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (x16989586621680180250 :: k1) = Let6989586621680180255Scrutinee_6989586621680180131Sym1 x16989586621680180250 :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621680180309Scrutinee_6989586621680180117Sym1 x6989586621680180308 :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) (x06989586621680180303 :: k2) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621680180309Scrutinee_6989586621680180117Sym1 x6989586621680180308 :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) (x06989586621680180303 :: k2) = Let6989586621680180309Scrutinee_6989586621680180117Sym2 x6989586621680180308 x06989586621680180303 :: TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type
type Apply (Lambda_6989586621681500761Sym3 x6989586621681500760 p6989586621681500756 a_69895866216815007496989586621681500757 :: TyFun Bool ([k1] ~> [k1]) -> Type) (flg6989586621681500763 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Monad

type Apply (Lambda_6989586621681500761Sym3 x6989586621681500760 p6989586621681500756 a_69895866216815007496989586621681500757 :: TyFun Bool ([k1] ~> [k1]) -> Type) (flg6989586621681500763 :: Bool) = Lambda_6989586621681500761Sym4 x6989586621681500760 p6989586621681500756 a_69895866216815007496989586621681500757 flg6989586621681500763
type Apply (Let6989586621680180218Scrutinee_6989586621680180141Sym1 x16989586621680180213 :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (x26989586621680180214 :: k2) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621680180218Scrutinee_6989586621680180141Sym1 x16989586621680180213 :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (x26989586621680180214 :: k2) = Let6989586621680180218Scrutinee_6989586621680180141Sym2 x16989586621680180213 x26989586621680180214 :: TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621680180255Scrutinee_6989586621680180131Sym1 x16989586621680180250 :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (x26989586621680180251 :: k2) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621680180255Scrutinee_6989586621680180131Sym1 x16989586621680180250 :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (x26989586621680180251 :: k2) = Let6989586621680180255Scrutinee_6989586621680180131Sym2 x16989586621680180250 x26989586621680180251 :: TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621680180309Scrutinee_6989586621680180117Sym2 x6989586621680180308 x06989586621680180303 :: TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) (y6989586621680180304 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621680180309Scrutinee_6989586621680180117Sym2 x6989586621680180308 x06989586621680180303 :: TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) (y6989586621680180304 :: k1) = Let6989586621680180309Scrutinee_6989586621680180117Sym3 x6989586621680180308 x06989586621680180303 y6989586621680180304 :: TyFun k3 (TyFun k4 Bool -> Type) -> Type
type Apply (Let6989586621680180218Scrutinee_6989586621680180141Sym2 x16989586621680180213 x26989586621680180214 :: TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) (y6989586621680180215 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621680180218Scrutinee_6989586621680180141Sym2 x16989586621680180213 x26989586621680180214 :: TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) (y6989586621680180215 :: k1) = Let6989586621680180218Scrutinee_6989586621680180141Sym3 x16989586621680180213 x26989586621680180214 y6989586621680180215 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type
type Apply (Let6989586621680180255Scrutinee_6989586621680180131Sym2 x16989586621680180250 x26989586621680180251 :: TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) (y6989586621680180252 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621680180255Scrutinee_6989586621680180131Sym2 x16989586621680180250 x26989586621680180251 :: TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) (y6989586621680180252 :: k1) = Let6989586621680180255Scrutinee_6989586621680180131Sym3 x16989586621680180250 x26989586621680180251 y6989586621680180252 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type
type Apply (Let6989586621680180309Scrutinee_6989586621680180117Sym3 x6989586621680180308 x06989586621680180303 y6989586621680180304 :: TyFun k3 (TyFun k4 Bool -> Type) -> Type) (arg_69895866216801801136989586621680180299 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621680180309Scrutinee_6989586621680180117Sym3 x6989586621680180308 x06989586621680180303 y6989586621680180304 :: TyFun k3 (TyFun k4 Bool -> Type) -> Type) (arg_69895866216801801136989586621680180299 :: k3) = Let6989586621680180309Scrutinee_6989586621680180117Sym4 x6989586621680180308 x06989586621680180303 y6989586621680180304 arg_69895866216801801136989586621680180299 :: TyFun k4 Bool -> Type
type Apply (Let6989586621680180218Scrutinee_6989586621680180141Sym3 x16989586621680180213 x26989586621680180214 y6989586621680180215 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) (arg_69895866216801801356989586621680180208 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621680180218Scrutinee_6989586621680180141Sym3 x16989586621680180213 x26989586621680180214 y6989586621680180215 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) (arg_69895866216801801356989586621680180208 :: k3) = Let6989586621680180218Scrutinee_6989586621680180141Sym4 x16989586621680180213 x26989586621680180214 y6989586621680180215 arg_69895866216801801356989586621680180208 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type
type Apply (Let6989586621680180255Scrutinee_6989586621680180131Sym3 x16989586621680180250 x26989586621680180251 y6989586621680180252 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) (arg_69895866216801801256989586621680180245 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621680180255Scrutinee_6989586621680180131Sym3 x16989586621680180250 x26989586621680180251 y6989586621680180252 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) (arg_69895866216801801256989586621680180245 :: k3) = Let6989586621680180255Scrutinee_6989586621680180131Sym4 x16989586621680180250 x26989586621680180251 y6989586621680180252 arg_69895866216801801256989586621680180245 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type
type Apply (Let6989586621680180218Scrutinee_6989586621680180141Sym4 x16989586621680180213 x26989586621680180214 y6989586621680180215 arg_69895866216801801356989586621680180208 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type) (arg_69895866216801801376989586621680180209 :: k4) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621680180218Scrutinee_6989586621680180141Sym4 x16989586621680180213 x26989586621680180214 y6989586621680180215 arg_69895866216801801356989586621680180208 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type) (arg_69895866216801801376989586621680180209 :: k4) = Let6989586621680180218Scrutinee_6989586621680180141Sym5 x16989586621680180213 x26989586621680180214 y6989586621680180215 arg_69895866216801801356989586621680180208 arg_69895866216801801376989586621680180209 :: TyFun k5 Bool -> Type
type Apply (Let6989586621680180255Scrutinee_6989586621680180131Sym4 x16989586621680180250 x26989586621680180251 y6989586621680180252 arg_69895866216801801256989586621680180245 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type) (arg_69895866216801801276989586621680180246 :: k4) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621680180255Scrutinee_6989586621680180131Sym4 x16989586621680180250 x26989586621680180251 y6989586621680180252 arg_69895866216801801256989586621680180245 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type) (arg_69895866216801801276989586621680180246 :: k4) = Let6989586621680180255Scrutinee_6989586621680180131Sym5 x16989586621680180250 x26989586621680180251 y6989586621680180252 arg_69895866216801801256989586621680180245 arg_69895866216801801276989586621680180246 :: TyFun k5 Bool -> Type
type Eval (IsPrefixOf xs ys :: Bool -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (IsPrefixOf xs ys :: Bool -> Type) = IsPrefixOf_ xs ys
type Eval (IsSuffixOf xs ys :: Bool -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (IsSuffixOf xs ys :: Bool -> Type) = Eval (IsPrefixOf ((Reverse :: [a] -> [a] -> Type) @@ xs) ((Reverse :: [a] -> [a] -> Type) @@ ys))
type Eval (IsInfixOf xs ys :: Bool -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (IsInfixOf xs ys :: Bool -> Type) = Eval ((Any (IsPrefixOf xs) :: [[a]] -> Bool -> Type) =<< Tails ys)
type Eval (Elem a2 as :: Bool -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (Elem a2 as :: Bool -> Type) = Eval ((IsJust :: Maybe Nat -> Bool -> Type) =<< FindIndex (TyEq a2 :: a1 -> Bool -> Type) as)
type Eval (IsLeft ('Right _a :: Either a b) :: Bool -> Type) 
Instance details

Defined in Fcf.Data.Common

type Eval (IsLeft ('Right _a :: Either a b) :: Bool -> Type) = 'False
type Eval (IsLeft ('Left _a :: Either a b) :: Bool -> Type) 
Instance details

Defined in Fcf.Data.Common

type Eval (IsLeft ('Left _a :: Either a b) :: Bool -> Type) = 'True
type Eval (IsRight ('Right _a :: Either a b) :: Bool -> Type) 
Instance details

Defined in Fcf.Data.Common

type Eval (IsRight ('Right _a :: Either a b) :: Bool -> Type) = 'True
type Eval (IsRight ('Left _a :: Either a b) :: Bool -> Type) 
Instance details

Defined in Fcf.Data.Common

type Eval (IsRight ('Left _a :: Either a b) :: Bool -> Type) = 'False
type Eval (TyEq a b :: Bool -> Type) 
Instance details

Defined in Fcf.Utils

type Eval (TyEq a b :: Bool -> Type) = TyEqImpl a b
type Eval (All p lst :: Bool -> Type) 
Instance details

Defined in Fcf.Class.Foldable

type Eval (All p lst :: Bool -> Type) = Eval (Foldr (Bicomap p (Pure :: Bool -> Bool -> Type) (&&)) 'True lst)
type Eval (Any p lst :: Bool -> Type) 
Instance details

Defined in Fcf.Class.Foldable

type Eval (Any p lst :: Bool -> Type) = Eval (Foldr (Bicomap p (Pure :: Bool -> Bool -> Type) (||)) 'False lst)
type Eval (TyEqSing a b :: Bool -> Type) 
Instance details

Defined in Util.Fcf

type Eval (TyEqSing a b :: Bool -> Type) = DefaultEq a b
type Apply OrSym0 (a6989586621680379592 :: [Bool]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply OrSym0 (a6989586621680379592 :: [Bool]) = OrSym1 a6989586621680379592
type Apply AndSym0 (a6989586621680379597 :: [Bool]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply AndSym0 (a6989586621680379597 :: [Bool]) = AndSym1 a6989586621680379597
type Apply (ListnullSym0 :: TyFun [a] Bool -> Type) (a6989586621680748691 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal.Disambiguation

type Apply (ListnullSym0 :: TyFun [a] Bool -> Type) (a6989586621680748691 :: [a]) = ListnullSym1 a6989586621680748691
type Apply (NullSym0 :: TyFun [a] Bool -> Type) (a6989586621680379770 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (NullSym0 :: TyFun [a] Bool -> Type) (a6989586621680379770 :: [a]) = NullSym1 a6989586621680379770
type Apply (Null_6989586621680822604Sym0 :: TyFun [a] Bool -> Type) (a6989586621680822610 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Null_6989586621680822604Sym0 :: TyFun [a] Bool -> Type) (a6989586621680822610 :: [a]) = Null_6989586621680822604Sym1 a6989586621680822610
type Apply (IsNothingSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679958803 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (IsNothingSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679958803 :: Maybe a) = IsNothingSym1 a6989586621679958803
type Apply (IsJustSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679958806 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (IsJustSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679958806 :: Maybe a) = IsJustSym1 a6989586621679958806
type Apply (AndSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680821979 :: t Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AndSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680821979 :: t Bool) = AndSym1 a6989586621680821979
type Apply (OrSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680821973 :: t Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (OrSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680821973 :: t Bool) = OrSym1 a6989586621680821973
type Apply (Null_6989586621681012013Sym0 :: TyFun (Identity a) Bool -> Type) (a6989586621681012017 :: Identity a) 
Instance details

Defined in Data.Singletons.Prelude.Identity

type Apply (Null_6989586621681012013Sym0 :: TyFun (Identity a) Bool -> Type) (a6989586621681012017 :: Identity a) = Null_6989586621681012013Sym1 a6989586621681012017
type Apply (Null_6989586621680823010Sym0 :: TyFun (Dual a) Bool -> Type) (a6989586621680823014 :: Dual a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Null_6989586621680823010Sym0 :: TyFun (Dual a) Bool -> Type) (a6989586621680823014 :: Dual a) = Null_6989586621680823010Sym1 a6989586621680823014
type Apply (Null_6989586621680823185Sym0 :: TyFun (Sum a) Bool -> Type) (a6989586621680823189 :: Sum a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Null_6989586621680823185Sym0 :: TyFun (Sum a) Bool -> Type) (a6989586621680823189 :: Sum a) = Null_6989586621680823185Sym1 a6989586621680823189
type Apply (Null_6989586621680823360Sym0 :: TyFun (Product a) Bool -> Type) (a6989586621680823364 :: Product a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Null_6989586621680823360Sym0 :: TyFun (Product a) Bool -> Type) (a6989586621680823364 :: Product a) = Null_6989586621680823360Sym1 a6989586621680823364
type Apply (ListelemSym1 a6989586621680748782 :: TyFun [a] Bool -> Type) (a6989586621680748783 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal.Disambiguation

type Apply (ListelemSym1 a6989586621680748782 :: TyFun [a] Bool -> Type) (a6989586621680748783 :: [a]) = ListelemSym2 a6989586621680748782 a6989586621680748783
type Apply (ListisPrefixOfSym1 a6989586621680748854 :: TyFun [a] Bool -> Type) (a6989586621680748855 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal.Disambiguation

type Apply (ListisPrefixOfSym1 a6989586621680748854 :: TyFun [a] Bool -> Type) (a6989586621680748855 :: [a]) = ListisPrefixOfSym2 a6989586621680748854 a6989586621680748855
type Apply (NotElemSym1 a6989586621680379352 :: TyFun [a] Bool -> Type) (a6989586621680379353 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (NotElemSym1 a6989586621680379352 :: TyFun [a] Bool -> Type) (a6989586621680379353 :: [a]) = NotElemSym2 a6989586621680379352 a6989586621680379353
type Apply (ElemSym1 a6989586621680379360 :: TyFun [a] Bool -> Type) (a6989586621680379361 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ElemSym1 a6989586621680379360 :: TyFun [a] Bool -> Type) (a6989586621680379361 :: [a]) = ElemSym2 a6989586621680379360 a6989586621680379361
type Apply (IsPrefixOfSym1 a6989586621680379382 :: TyFun [a] Bool -> Type) (a6989586621680379383 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IsPrefixOfSym1 a6989586621680379382 :: TyFun [a] Bool -> Type) (a6989586621680379383 :: [a]) = IsPrefixOfSym2 a6989586621680379382 a6989586621680379383
type Apply (AnySym1 a6989586621680379577 :: TyFun [a] Bool -> Type) (a6989586621680379578 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (AnySym1 a6989586621680379577 :: TyFun [a] Bool -> Type) (a6989586621680379578 :: [a]) = AnySym2 a6989586621680379577 a6989586621680379578
type Apply (IsInfixOfSym1 a6989586621680379368 :: TyFun [a] Bool -> Type) (a6989586621680379369 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IsInfixOfSym1 a6989586621680379368 :: TyFun [a] Bool -> Type) (a6989586621680379369 :: [a]) = IsInfixOfSym2 a6989586621680379368 a6989586621680379369
type Apply (AllSym1 a6989586621680379585 :: TyFun [a] Bool -> Type) (a6989586621680379586 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (AllSym1 a6989586621680379585 :: TyFun [a] Bool -> Type) (a6989586621680379586 :: [a]) = AllSym2 a6989586621680379585 a6989586621680379586
type Apply (IsSuffixOfSym1 a6989586621680379375 :: TyFun [a] Bool -> Type) (a6989586621680379376 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IsSuffixOfSym1 a6989586621680379375 :: TyFun [a] Bool -> Type) (a6989586621680379376 :: [a]) = IsSuffixOfSym2 a6989586621680379375 a6989586621680379376
type Apply (Elem_6989586621680822470Sym1 a6989586621680822479 :: TyFun [a] Bool -> Type) (a6989586621680822480 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680822470Sym1 a6989586621680822479 :: TyFun [a] Bool -> Type) (a6989586621680822480 :: [a]) = Elem_6989586621680822470Sym2 a6989586621680822479 a6989586621680822480
type Apply (Elem_6989586621681011897Sym1 a6989586621681011902 :: TyFun (Identity a) Bool -> Type) (a6989586621681011903 :: Identity a) 
Instance details

Defined in Data.Singletons.Prelude.Identity

type Apply (Elem_6989586621681011897Sym1 a6989586621681011902 :: TyFun (Identity a) Bool -> Type) (a6989586621681011903 :: Identity a) = Elem_6989586621681011897Sym2 a6989586621681011902 a6989586621681011903
type Apply (Elem_6989586621680822878Sym1 a6989586621680822887 :: TyFun (Dual a) Bool -> Type) (a6989586621680822888 :: Dual a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680822878Sym1 a6989586621680822887 :: TyFun (Dual a) Bool -> Type) (a6989586621680822888 :: Dual a) = Elem_6989586621680822878Sym2 a6989586621680822887 a6989586621680822888
type Apply (Elem_6989586621680823053Sym1 a6989586621680823062 :: TyFun (Sum a) Bool -> Type) (a6989586621680823063 :: Sum a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680823053Sym1 a6989586621680823062 :: TyFun (Sum a) Bool -> Type) (a6989586621680823063 :: Sum a) = Elem_6989586621680823053Sym2 a6989586621680823062 a6989586621680823063
type Apply (Elem_6989586621680823228Sym1 a6989586621680823237 :: TyFun (Product a) Bool -> Type) (a6989586621680823238 :: Product a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680823228Sym1 a6989586621680823237 :: TyFun (Product a) Bool -> Type) (a6989586621680823238 :: Product a) = Elem_6989586621680823228Sym2 a6989586621680823237 a6989586621680823238
type Apply (Elem_bySym2 a6989586621680378588 a6989586621680378589 :: TyFun [a] Bool -> Type) (a6989586621680378590 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Elem_bySym2 a6989586621680378588 a6989586621680378589 :: TyFun [a] Bool -> Type) (a6989586621680378590 :: [a]) = Elem_bySym3 a6989586621680378588 a6989586621680378589 a6989586621680378590
type Apply (Elem_6989586621680822360Sym1 a6989586621680822369 :: TyFun (t a) Bool -> Type) (a6989586621680822370 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680822360Sym1 a6989586621680822369 :: TyFun (t a) Bool -> Type) (a6989586621680822370 :: t a) = Elem_6989586621680822360Sym2 a6989586621680822369 a6989586621680822370
type Apply (Null_6989586621680822324Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680822330 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Null_6989586621680822324Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680822330 :: t a) = Null_6989586621680822324Sym1 a6989586621680822330
type Apply (AnySym1 a6989586621680821965 :: TyFun (t a) Bool -> Type) (a6989586621680821966 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AnySym1 a6989586621680821965 :: TyFun (t a) Bool -> Type) (a6989586621680821966 :: t a) = AnySym2 a6989586621680821965 a6989586621680821966
type Apply (ElemSym1 a6989586621680822160 :: TyFun (t a) Bool -> Type) (a6989586621680822161 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ElemSym1 a6989586621680822160 :: TyFun (t a) Bool -> Type) (a6989586621680822161 :: t a) = ElemSym2 a6989586621680822160 a6989586621680822161
type Apply (NotElemSym1 a6989586621680821907 :: TyFun (t a) Bool -> Type) (a6989586621680821908 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (NotElemSym1 a6989586621680821907 :: TyFun (t a) Bool -> Type) (a6989586621680821908 :: t a) = NotElemSym2 a6989586621680821907 a6989586621680821908
type Apply (NullSym0 :: TyFun (t a) Bool -> Type) (a6989586621680822153 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (NullSym0 :: TyFun (t a) Bool -> Type) (a6989586621680822153 :: t a) = NullSym1 a6989586621680822153
type Apply (AllSym1 a6989586621680821956 :: TyFun (t a) Bool -> Type) (a6989586621680821957 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AllSym1 a6989586621680821956 :: TyFun (t a) Bool -> Type) (a6989586621680821957 :: t a) = AllSym2 a6989586621680821956 a6989586621680821957
type Apply (ListisPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621680748854 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal.Disambiguation

type Apply (ListisPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621680748854 :: [a]) = ListisPrefixOfSym1 a6989586621680748854
type Apply (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621680379382 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621680379382 :: [a]) = IsPrefixOfSym1 a6989586621680379382
type Apply (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621680379368 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621680379368 :: [a]) = IsInfixOfSym1 a6989586621680379368
type Apply (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621680379375 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621680379375 :: [a]) = IsSuffixOfSym1 a6989586621680379375
type Apply (Let6989586621680378901Scrutinee_6989586621680375080Sym1 x6989586621680378899 :: TyFun [a] (TyFun (k1 ~> Bool) (TyFun k Bool -> Type) -> Type) -> Type) (xs6989586621680378900 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680378901Scrutinee_6989586621680375080Sym1 x6989586621680378899 :: TyFun [a] (TyFun (k1 ~> Bool) (TyFun k Bool -> Type) -> Type) -> Type) (xs6989586621680378900 :: [a]) = Let6989586621680378901Scrutinee_6989586621680375080Sym2 x6989586621680378899 xs6989586621680378900 :: TyFun (k1 ~> Bool) (TyFun k Bool -> Type) -> Type
type Apply (Let6989586621680378609Scrutinee_6989586621680375108Sym2 y6989586621680378606 ys6989586621680378607 :: TyFun [k1] (TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type) -> Type) (xs6989586621680378608 :: [k1]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680378609Scrutinee_6989586621680375108Sym2 y6989586621680378606 ys6989586621680378607 :: TyFun [k1] (TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type) -> Type) (xs6989586621680378608 :: [k1]) = Let6989586621680378609Scrutinee_6989586621680375108Sym3 y6989586621680378606 ys6989586621680378607 xs6989586621680378608 :: TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type
type Apply (Let6989586621680378625Scrutinee_6989586621680375106Sym2 x6989586621680378622 xs6989586621680378623 :: TyFun [k1] (TyFun k3 Bool -> Type) -> Type) (ls6989586621680378624 :: [k1]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680378625Scrutinee_6989586621680375106Sym2 x6989586621680378622 xs6989586621680378623 :: TyFun [k1] (TyFun k3 Bool -> Type) -> Type) (ls6989586621680378624 :: [k1]) = Let6989586621680378625Scrutinee_6989586621680375106Sym3 x6989586621680378622 xs6989586621680378623 ls6989586621680378624 :: TyFun k3 Bool -> Type
type Apply (Null_6989586621680822765Sym0 :: TyFun (Either a1 a2) Bool -> Type) (a6989586621680822771 :: Either a1 a2) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Null_6989586621680822765Sym0 :: TyFun (Either a1 a2) Bool -> Type) (a6989586621680822771 :: Either a1 a2) = Null_6989586621680822765Sym1 a6989586621680822771
type Apply (IsRightSym0 :: TyFun (Either a b) Bool -> Type) (a6989586621680803379 :: Either a b) 
Instance details

Defined in Data.Singletons.Prelude.Either

type Apply (IsRightSym0 :: TyFun (Either a b) Bool -> Type) (a6989586621680803379 :: Either a b) = IsRightSym1 a6989586621680803379
type Apply (IsLeftSym0 :: TyFun (Either a b) Bool -> Type) (a6989586621680803382 :: Either a b) 
Instance details

Defined in Data.Singletons.Prelude.Either

type Apply (IsLeftSym0 :: TyFun (Either a b) Bool -> Type) (a6989586621680803382 :: Either a b) = IsLeftSym1 a6989586621680803382
type Apply (Elem_6989586621680822846Sym1 a6989586621680822851 :: TyFun (Proxy a) Bool -> Type) (a6989586621680822852 :: Proxy a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680822846Sym1 a6989586621680822851 :: TyFun (Proxy a) Bool -> Type) (a6989586621680822852 :: Proxy a) = Elem_6989586621680822846Sym2 a6989586621680822851 a6989586621680822852
type Apply (Null_6989586621680822839Sym0 :: TyFun (Proxy a) Bool -> Type) (a6989586621680822843 :: Proxy a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Null_6989586621680822839Sym0 :: TyFun (Proxy a) Bool -> Type) (a6989586621680822843 :: Proxy a) = Null_6989586621680822839Sym1 a6989586621680822843
type Apply (TFHelper_6989586621681202942Sym1 a6989586621681202947 :: TyFun (Arg a b) Bool -> Type) (a6989586621681202948 :: Arg a b) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Apply (TFHelper_6989586621681202942Sym1 a6989586621681202947 :: TyFun (Arg a b) Bool -> Type) (a6989586621681202948 :: Arg a b) = TFHelper_6989586621681202942Sym2 a6989586621681202947 a6989586621681202948
type Apply (TFHelper_6989586621680786553Sym1 a6989586621680786558 :: TyFun (Proxy s) Bool -> Type) (a6989586621680786559 :: Proxy s) 
Instance details

Defined in Data.Singletons.Prelude.Proxy

type Apply (TFHelper_6989586621680786553Sym1 a6989586621680786558 :: TyFun (Proxy s) Bool -> Type) (a6989586621680786559 :: Proxy s) = TFHelper_6989586621680786553Sym2 a6989586621680786558 a6989586621680786559
type Apply (ListnubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) (a6989586621680748816 :: a ~> (a ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal.Disambiguation

type Apply (ListnubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) (a6989586621680748816 :: a ~> (a ~> Bool)) = ListnubBySym1 a6989586621680748816
type Apply (ListpartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621680748876 :: a ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal.Disambiguation

type Apply (ListpartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621680748876 :: a ~> Bool) = ListpartitionSym1 a6989586621680748876
type Apply (ListfilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621680748887 :: a ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal.Disambiguation

type Apply (ListfilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621680748887 :: a ~> Bool) = ListfilterSym1 a6989586621680748887
type Apply (ListspanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621680748898 :: a ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal.Disambiguation

type Apply (ListspanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621680748898 :: a ~> Bool) = ListspanSym1 a6989586621680748898
type Apply (ListdropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621680748909 :: a ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal.Disambiguation

type Apply (ListdropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621680748909 :: a ~> Bool) = ListdropWhileSym1 a6989586621680748909
type Apply (ListtakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621680748920 :: a ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal.Disambiguation

type Apply (ListtakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621680748920 :: a ~> Bool) = ListtakeWhileSym1 a6989586621680748920
type Apply (Elem_bySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> Bool)) -> Type) (a6989586621680378588 :: a ~> (a ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Elem_bySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> Bool)) -> Type) (a6989586621680378588 :: a ~> (a ~> Bool)) = Elem_bySym1 a6989586621680378588
type Apply (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) (a6989586621680378598 :: a ~> (a ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) (a6989586621680378598 :: a ~> (a ~> Bool)) = NubBySym1 a6989586621680378598
type Apply (SelectSym0 :: TyFun (a ~> Bool) (a ~> (([a], [a]) ~> ([a], [a]))) -> Type) (a6989586621680378694 :: a ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (SelectSym0 :: TyFun (a ~> Bool) (a ~> (([a], [a]) ~> ([a], [a]))) -> Type) (a6989586621680378694 :: a ~> Bool) = SelectSym1 a6989586621680378694
type Apply (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621680378709 :: a ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621680378709 :: a ~> Bool) = PartitionSym1 a6989586621680378709
type Apply (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621680378821 :: a ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621680378821 :: a ~> Bool) = BreakSym1 a6989586621680378821
type Apply (Let6989586621680378834YsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621680378825 :: k ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680378834YsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621680378825 :: k ~> Bool) = Let6989586621680378834YsSym1 p6989586621680378825
type Apply (Let6989586621680378834ZsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621680378825 :: k ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680378834ZsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621680378825 :: k ~> Bool) = Let6989586621680378834ZsSym1 p6989586621680378825
type Apply (Let6989586621680378834X_6989586621680378835Sym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] ([k], [k]) -> Type) -> Type) -> Type) (p6989586621680378825 :: k ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680378834X_6989586621680378835Sym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] ([k], [k]) -> Type) -> Type) -> Type) (p6989586621680378825 :: k ~> Bool) = Let6989586621680378834X_6989586621680378835Sym1 p6989586621680378825
type Apply (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621680378856 :: a ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621680378856 :: a ~> Bool) = SpanSym1 a6989586621680378856
type Apply (Let6989586621680378869YsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621680378860 :: k ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680378869YsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621680378860 :: k ~> Bool) = Let6989586621680378869YsSym1 p6989586621680378860
type Apply (Let6989586621680378869ZsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621680378860 :: k ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680378869ZsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621680378860 :: k ~> Bool) = Let6989586621680378869ZsSym1 p6989586621680378860
type Apply (Let6989586621680378869X_6989586621680378870Sym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] ([k], [k]) -> Type) -> Type) -> Type) (p6989586621680378860 :: k ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680378869X_6989586621680378870Sym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] ([k], [k]) -> Type) -> Type) -> Type) (p6989586621680378860 :: k ~> Bool) = Let6989586621680378869X_6989586621680378870Sym1 p6989586621680378860
type Apply (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) (a6989586621680378731 :: a ~> (a ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) (a6989586621680378731 :: a ~> (a ~> Bool)) = GroupBySym1 a6989586621680378731
type Apply (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621680378910 :: a ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621680378910 :: a ~> Bool) = DropWhileSym1 a6989586621680378910
type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621680378925 :: a ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621680378925 :: a ~> Bool) = TakeWhileSym1 a6989586621680378925
type Apply (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621680379025 :: a ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621680379025 :: a ~> Bool) = FilterSym1 a6989586621680379025
type Apply (FindSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe a) -> Type) (a6989586621680379018 :: a ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FindSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe a) -> Type) (a6989586621680379018 :: a ~> Bool) = FindSym1 a6989586621680379018
type Apply (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) (a6989586621680379124 :: a ~> (a ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) (a6989586621680379124 :: a ~> (a ~> Bool)) = DeleteBySym1 a6989586621680379124
type Apply (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621680379114 :: a ~> (a ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621680379114 :: a ~> (a ~> Bool)) = DeleteFirstsBySym1 a6989586621680379114
type Apply (UnionBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621680378578 :: a ~> (a ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (UnionBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621680378578 :: a ~> (a ~> Bool)) = UnionBySym1 a6989586621680378578
type Apply (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Nat]) -> Type) (a6989586621680378968 :: a ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Nat]) -> Type) (a6989586621680378968 :: a ~> Bool) = FindIndicesSym1 a6989586621680378968
type Apply (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Nat) -> Type) (a6989586621680378991 :: a ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Nat) -> Type) (a6989586621680378991 :: a ~> Bool) = FindIndexSym1 a6989586621680378991
type Apply (AnySym0 :: TyFun (a ~> Bool) ([a] ~> Bool) -> Type) (a6989586621680379577 :: a ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (AnySym0 :: TyFun (a ~> Bool) ([a] ~> Bool) -> Type) (a6989586621680379577 :: a ~> Bool) = AnySym1 a6989586621680379577
type Apply (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621680378939 :: a ~> (a ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621680378939 :: a ~> (a ~> Bool)) = IntersectBySym1 a6989586621680378939
type Apply (AllSym0 :: TyFun (a ~> Bool) ([a] ~> Bool) -> Type) (a6989586621680379585 :: a ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (AllSym0 :: TyFun (a ~> Bool) ([a] ~> Bool) -> Type) (a6989586621680379585 :: a ~> Bool) = AllSym1 a6989586621680379585
type Apply (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621680378893 :: a ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621680378893 :: a ~> Bool) = DropWhileEndSym1 a6989586621680378893
type Apply (UntilSym0 :: TyFun (a ~> Bool) ((a ~> a) ~> (a ~> a)) -> Type) (a6989586621679989617 :: a ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (UntilSym0 :: TyFun (a ~> Bool) ((a ~> a) ~> (a ~> a)) -> Type) (a6989586621679989617 :: a ~> Bool) = UntilSym1 a6989586621679989617
type Apply (TFHelper_6989586621681202942Sym0 :: TyFun (Arg a b) (Arg a b ~> Bool) -> Type) (a6989586621681202947 :: Arg a b) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Apply (TFHelper_6989586621681202942Sym0 :: TyFun (Arg a b) (Arg a b ~> Bool) -> Type) (a6989586621681202947 :: Arg a b) = TFHelper_6989586621681202942Sym1 a6989586621681202947
type Apply (TFHelper_6989586621680786553Sym0 :: TyFun (Proxy s) (Proxy s ~> Bool) -> Type) (a6989586621680786558 :: Proxy s) 
Instance details

Defined in Data.Singletons.Prelude.Proxy

type Apply (TFHelper_6989586621680786553Sym0 :: TyFun (Proxy s) (Proxy s ~> Bool) -> Type) (a6989586621680786558 :: Proxy s) = TFHelper_6989586621680786553Sym1 a6989586621680786558
type Apply (MfilterSym0 :: TyFun (a ~> Bool) (m a ~> m a) -> Type) (a6989586621681500592 :: a ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Monad

type Apply (MfilterSym0 :: TyFun (a ~> Bool) (m a ~> m a) -> Type) (a6989586621681500592 :: a ~> Bool) = MfilterSym1 a6989586621681500592 :: TyFun (m a) (m a) -> Type
type Apply (FilterMSym0 :: TyFun (a ~> m Bool) ([a] ~> m [a]) -> Type) (a6989586621681500754 :: a ~> m Bool) 
Instance details

Defined in Data.Singletons.Prelude.Monad

type Apply (FilterMSym0 :: TyFun (a ~> m Bool) ([a] ~> m [a]) -> Type) (a6989586621681500754 :: a ~> m Bool) = FilterMSym1 a6989586621681500754
type Apply (Let6989586621680378602NubBy'Sym0 :: TyFun (k1 ~> (k1 ~> Bool)) (TyFun k (TyFun [k1] ([k1] ~> [k1]) -> Type) -> Type) -> Type) (eq6989586621680378600 :: k1 ~> (k1 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680378602NubBy'Sym0 :: TyFun (k1 ~> (k1 ~> Bool)) (TyFun k (TyFun [k1] ([k1] ~> [k1]) -> Type) -> Type) -> Type) (eq6989586621680378600 :: k1 ~> (k1 ~> Bool)) = Let6989586621680378602NubBy'Sym1 eq6989586621680378600 :: TyFun k (TyFun [k1] ([k1] ~> [k1]) -> Type) -> Type
type Apply (Let6989586621680378736YsSym0 :: TyFun (k1 ~> (a ~> Bool)) (TyFun k1 (TyFun [a] [a] -> Type) -> Type) -> Type) (eq6989586621680378733 :: k1 ~> (a ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680378736YsSym0 :: TyFun (k1 ~> (a ~> Bool)) (TyFun k1 (TyFun [a] [a] -> Type) -> Type) -> Type) (eq6989586621680378733 :: k1 ~> (a ~> Bool)) = Let6989586621680378736YsSym1 eq6989586621680378733
type Apply (Let6989586621680378736ZsSym0 :: TyFun (k1 ~> (a ~> Bool)) (TyFun k1 (TyFun [a] [a] -> Type) -> Type) -> Type) (eq6989586621680378733 :: k1 ~> (a ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680378736ZsSym0 :: TyFun (k1 ~> (a ~> Bool)) (TyFun k1 (TyFun [a] [a] -> Type) -> Type) -> Type) (eq6989586621680378733 :: k1 ~> (a ~> Bool)) = Let6989586621680378736ZsSym1 eq6989586621680378733
type Apply (Let6989586621680378736X_6989586621680378737Sym0 :: TyFun (k1 ~> (a ~> Bool)) (TyFun k1 (TyFun [a] ([a], [a]) -> Type) -> Type) -> Type) (eq6989586621680378733 :: k1 ~> (a ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680378736X_6989586621680378737Sym0 :: TyFun (k1 ~> (a ~> Bool)) (TyFun k1 (TyFun [a] ([a], [a]) -> Type) -> Type) -> Type) (eq6989586621680378733 :: k1 ~> (a ~> Bool)) = Let6989586621680378736X_6989586621680378737Sym1 eq6989586621680378733
type Apply (Lambda_6989586621680378897Sym0 :: TyFun (a ~> Bool) (TyFun k (TyFun a (TyFun [a] [a] -> Type) -> Type) -> Type) -> Type) (p6989586621680378895 :: a ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Lambda_6989586621680378897Sym0 :: TyFun (a ~> Bool) (TyFun k (TyFun a (TyFun [a] [a] -> Type) -> Type) -> Type) -> Type) (p6989586621680378895 :: a ~> Bool) = Lambda_6989586621680378897Sym1 p6989586621680378895 :: TyFun k (TyFun a (TyFun [a] [a] -> Type) -> Type) -> Type
type Apply (Lambda_6989586621680821893Sym0 :: TyFun (a ~> Bool) (TyFun k (TyFun a (First a) -> Type) -> Type) -> Type) (p6989586621680821891 :: a ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Lambda_6989586621680821893Sym0 :: TyFun (a ~> Bool) (TyFun k (TyFun a (First a) -> Type) -> Type) -> Type) (p6989586621680821891 :: a ~> Bool) = Lambda_6989586621680821893Sym1 p6989586621680821891 :: TyFun k (TyFun a (First a) -> Type) -> Type
type Apply (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621680821965 :: a ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621680821965 :: a ~> Bool) = AnySym1 a6989586621680821965 :: TyFun (t a) Bool -> Type
type Apply (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621680821956 :: a ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621680821956 :: a ~> Bool) = AllSym1 a6989586621680821956 :: TyFun (t a) Bool -> Type
type Apply (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) (a6989586621680821889 :: a ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) (a6989586621680821889 :: a ~> Bool) = FindSym1 a6989586621680821889 :: TyFun (t a) (Maybe a) -> Type
type Apply (Let6989586621679989623GoSym0 :: TyFun (k1 ~> Bool) (TyFun (k1 ~> k1) (TyFun k2 (TyFun k1 k1 -> Type) -> Type) -> Type) -> Type) (p6989586621679989620 :: k1 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (Let6989586621679989623GoSym0 :: TyFun (k1 ~> Bool) (TyFun (k1 ~> k1) (TyFun k2 (TyFun k1 k1 -> Type) -> Type) -> Type) -> Type) (p6989586621679989620 :: k1 ~> Bool) = Let6989586621679989623GoSym1 p6989586621679989620 :: TyFun (k1 ~> k1) (TyFun k2 (TyFun k1 k1 -> Type) -> Type) -> Type
type Apply (Lambda_6989586621681500596Sym0 :: TyFun (k1 ~> Bool) (TyFun k (TyFun k1 (m k1) -> Type) -> Type) -> Type) (p6989586621681500594 :: k1 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Monad

type Apply (Lambda_6989586621681500596Sym0 :: TyFun (k1 ~> Bool) (TyFun k (TyFun k1 (m k1) -> Type) -> Type) -> Type) (p6989586621681500594 :: k1 ~> Bool) = Lambda_6989586621681500596Sym1 p6989586621681500594 :: TyFun k (TyFun k1 (m k1) -> Type) -> Type
type Apply (Lambda_6989586621681500758Sym0 :: TyFun (k2 ~> f Bool) (TyFun k3 (TyFun k2 (f [k2] ~> f [k2]) -> Type) -> Type) -> Type) (p6989586621681500756 :: k2 ~> f Bool) 
Instance details

Defined in Data.Singletons.Prelude.Monad

type Apply (Lambda_6989586621681500758Sym0 :: TyFun (k2 ~> f Bool) (TyFun k3 (TyFun k2 (f [k2] ~> f [k2]) -> Type) -> Type) -> Type) (p6989586621681500756 :: k2 ~> f Bool) = Lambda_6989586621681500758Sym1 p6989586621681500756 :: TyFun k3 (TyFun k2 (f [k2] ~> f [k2]) -> Type) -> Type
type Apply (Lambda_6989586621680378950Sym0 :: TyFun (b ~> (a ~> Bool)) (TyFun k1 (TyFun k2 (TyFun a (TyFun [a] (TyFun b (m b) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (eq6989586621680378942 :: b ~> (a ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Lambda_6989586621680378950Sym0 :: TyFun (b ~> (a ~> Bool)) (TyFun k1 (TyFun k2 (TyFun a (TyFun [a] (TyFun b (m b) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (eq6989586621680378942 :: b ~> (a ~> Bool)) = Lambda_6989586621680378950Sym1 eq6989586621680378942 :: TyFun k1 (TyFun k2 (TyFun a (TyFun [a] (TyFun b (m b) -> Type) -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621680378901Scrutinee_6989586621680375080Sym2 x6989586621680378899 xs6989586621680378900 :: TyFun (k1 ~> Bool) (TyFun k Bool -> Type) -> Type) (p6989586621680378895 :: k1 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680378901Scrutinee_6989586621680375080Sym2 x6989586621680378899 xs6989586621680378900 :: TyFun (k1 ~> Bool) (TyFun k Bool -> Type) -> Type) (p6989586621680378895 :: k1 ~> Bool) = Let6989586621680378901Scrutinee_6989586621680375080Sym3 x6989586621680378899 xs6989586621680378900 p6989586621680378895 :: TyFun k Bool -> Type
type Apply (Let6989586621680378609Scrutinee_6989586621680375108Sym3 y6989586621680378606 ys6989586621680378607 xs6989586621680378608 :: TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type) (eq6989586621680378600 :: k1 ~> (k1 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680378609Scrutinee_6989586621680375108Sym3 y6989586621680378606 ys6989586621680378607 xs6989586621680378608 :: TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type) (eq6989586621680378600 :: k1 ~> (k1 ~> Bool)) = Let6989586621680378609Scrutinee_6989586621680375108Sym4 y6989586621680378606 ys6989586621680378607 xs6989586621680378608 eq6989586621680378600 :: TyFun k3 Bool -> Type

data ByteString #

A space-efficient representation of a Word8 vector, supporting many efficient operations.

A ByteString contains 8-bit bytes, or by using the operations from Data.ByteString.Char8 it can be interpreted as containing 8-bit characters.

Instances

Instances details
IsList ByteString

Since: bytestring-0.10.12.0

Instance details

Defined in Data.ByteString.Internal

Associated Types

type Item ByteString #

Eq ByteString 
Instance details

Defined in Data.ByteString.Internal

Data ByteString 
Instance details

Defined in Data.ByteString.Internal

Methods

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

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

toConstr :: ByteString -> Constr #

dataTypeOf :: ByteString -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ByteString 
Instance details

Defined in Data.ByteString.Internal

Read ByteString 
Instance details

Defined in Data.ByteString.Internal

Show ByteString 
Instance details

Defined in Data.ByteString.Internal

IsString ByteString

Beware: fromString truncates multi-byte characters to octets. e.g. "枯朶に烏のとまりけり秋の暮" becomes �6k�nh~�Q��n�

Instance details

Defined in Data.ByteString.Internal

Semigroup ByteString 
Instance details

Defined in Data.ByteString.Internal

Monoid ByteString 
Instance details

Defined in Data.ByteString.Internal

Hashable ByteString 
Instance details

Defined in Data.Hashable.Class

Chunk ByteString 
Instance details

Defined in Data.Attoparsec.Internal.Types

Associated Types

type ChunkElem ByteString #

NFData ByteString 
Instance details

Defined in Data.ByteString.Internal

Methods

rnf :: ByteString -> () #

FromBuilder ByteString 
Instance details

Defined in Fmt.Internal.Core

Ixed ByteString 
Instance details

Defined in Control.Lens.At

Stream ByteString 
Instance details

Defined in Text.Megaparsec.Stream

Associated Types

type Token ByteString #

type Tokens ByteString #

VisualStream ByteString 
Instance details

Defined in Text.Megaparsec.Stream

TraversableStream ByteString 
Instance details

Defined in Text.Megaparsec.Stream

Print ByteString 
Instance details

Defined in Universum.Print.Internal

Methods

hPutStr :: Handle -> ByteString -> IO () #

hPutStrLn :: Handle -> ByteString -> IO () #

Container ByteString 
Instance details

Defined in Universum.Container.Class

Associated Types

type Element ByteString #

One ByteString 
Instance details

Defined in Universum.Container.Class

Associated Types

type OneItem ByteString #

TypeHasDoc ByteString 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions ByteString :: FieldDescriptions #

IsoValue ByteString 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT ByteString :: T #

HasAnnotation ByteString Source # 
Instance details

Defined in Lorentz.Annotation

SliceOpHs ByteString Source # 
Instance details

Defined in Lorentz.Polymorphic

ConcatOpHs ByteString Source # 
Instance details

Defined in Lorentz.Polymorphic

SizeOpHs ByteString Source # 
Instance details

Defined in Lorentz.Polymorphic

BytesLike ByteString Source # 
Instance details

Defined in Lorentz.Bytes

ConvertUtf8 String ByteString 
Instance details

Defined in Universum.String.Conversion

ConvertUtf8 Text ByteString 
Instance details

Defined in Universum.String.Conversion

ConvertUtf8 Text ByteString 
Instance details

Defined in Universum.String.Conversion

Cons ByteString ByteString Word8 Word8 
Instance details

Defined in Control.Lens.Cons

Snoc ByteString ByteString Word8 Word8 
Instance details

Defined in Control.Lens.Cons

CanCastTo (TSignature a :: Type) ByteString Source # 
Instance details

Defined in Lorentz.Coercions

CanCastTo (Packed a :: Type) ByteString Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (Packed a) -> Proxy ByteString -> () Source #

CanCastTo (Hash alg a :: Type) ByteString Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (Hash alg a) -> Proxy ByteString -> () Source #

type State ByteString 
Instance details

Defined in Data.Attoparsec.Internal.Types

type State ByteString = Buffer
type ChunkElem ByteString 
Instance details

Defined in Data.Attoparsec.Internal.Types

type Item ByteString 
Instance details

Defined in Data.ByteString.Internal

type Index ByteString 
Instance details

Defined in Control.Lens.At

type IxValue ByteString 
Instance details

Defined in Control.Lens.At

type Tokens ByteString 
Instance details

Defined in Text.Megaparsec.Stream

type Token ByteString 
Instance details

Defined in Text.Megaparsec.Stream

type Element ByteString 
Instance details

Defined in Universum.Container.Class

type OneItem ByteString 
Instance details

Defined in Universum.Container.Class

type TypeDocFieldDescriptions ByteString 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type ToT ByteString 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT ByteString = 'TBytes

data Address #

Instances

Instances details
Eq Address 
Instance details

Defined in Tezos.Address

Methods

(==) :: Address -> Address -> Bool #

(/=) :: Address -> Address -> Bool #

Ord Address 
Instance details

Defined in Tezos.Address

Show Address 
Instance details

Defined in Tezos.Address

Generic Address 
Instance details

Defined in Tezos.Address

Associated Types

type Rep Address :: Type -> Type #

Methods

from :: Address -> Rep Address x #

to :: Rep Address x -> Address #

ToJSON Address 
Instance details

Defined in Tezos.Address

ToJSONKey Address 
Instance details

Defined in Tezos.Address

FromJSON Address 
Instance details

Defined in Tezos.Address

FromJSONKey Address 
Instance details

Defined in Tezos.Address

NFData Address 
Instance details

Defined in Tezos.Address

Methods

rnf :: Address -> () #

Buildable Address 
Instance details

Defined in Tezos.Address

Methods

build :: Address -> Builder #

HasCLReader Address 
Instance details

Defined in Tezos.Address

TypeHasDoc Address 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions Address :: FieldDescriptions #

IsoValue Address 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Address :: T #

HasAnnotation Address Source # 
Instance details

Defined in Lorentz.Annotation

ToAddress Address Source # 
Instance details

Defined in Lorentz.Address

FromContractRef cp Address Source # 
Instance details

Defined in Lorentz.Address

ToTAddress cp Address Source # 
Instance details

Defined in Lorentz.Address

CanCastTo Address (TAddress p :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy Address -> Proxy (TAddress p) -> () Source #

CanCastTo (TAddress p :: Type) Address Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (TAddress p) -> Proxy Address -> () Source #

type Rep Address 
Instance details

Defined in Tezos.Address

type Rep Address = D1 ('MetaData "Address" "Tezos.Address" "morley-1.14.0-inplace" 'False) (C1 ('MetaCons "KeyAddress" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 KeyHash)) :+: C1 ('MetaCons "ContractAddress" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ContractHash)))
type TypeDocFieldDescriptions Address 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type ToT Address 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT Address = 'TAddress

data EpAddress #

Constructors

EpAddress 

Instances

Instances details
Eq EpAddress 
Instance details

Defined in Michelson.Typed.Entrypoints

Ord EpAddress 
Instance details

Defined in Michelson.Typed.Entrypoints

Show EpAddress 
Instance details

Defined in Michelson.Typed.Entrypoints

Generic EpAddress 
Instance details

Defined in Michelson.Typed.Entrypoints

Associated Types

type Rep EpAddress :: Type -> Type #

NFData EpAddress 
Instance details

Defined in Michelson.Typed.Entrypoints

Methods

rnf :: EpAddress -> () #

Buildable EpAddress 
Instance details

Defined in Michelson.Typed.Entrypoints

Methods

build :: EpAddress -> Builder #

TypeHasDoc EpAddress 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions EpAddress :: FieldDescriptions #

IsoValue EpAddress 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT EpAddress :: T #

HasAnnotation EpAddress Source # 
Instance details

Defined in Lorentz.Annotation

ToAddress EpAddress Source # 
Instance details

Defined in Lorentz.Address

FromContractRef cp EpAddress Source # 
Instance details

Defined in Lorentz.Address

CanCastTo (FutureContract p :: Type) EpAddress Source # 
Instance details

Defined in Lorentz.Coercions

type Rep EpAddress 
Instance details

Defined in Michelson.Typed.Entrypoints

type Rep EpAddress = D1 ('MetaData "EpAddress" "Michelson.Typed.Entrypoints" "morley-1.14.0-inplace" 'False) (C1 ('MetaCons "EpAddress" 'PrefixI 'True) (S1 ('MetaSel ('Just "eaAddress") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Address) :*: S1 ('MetaSel ('Just "eaEntrypoint") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 EpName)))
type TypeDocFieldDescriptions EpAddress 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type ToT EpAddress 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT EpAddress = 'TAddress

data Mutez #

Instances

Instances details
Bounded Mutez 
Instance details

Defined in Tezos.Core

Enum Mutez 
Instance details

Defined in Tezos.Core

Eq Mutez 
Instance details

Defined in Tezos.Core

Methods

(==) :: Mutez -> Mutez -> Bool #

(/=) :: Mutez -> Mutez -> Bool #

Data Mutez 
Instance details

Defined in Tezos.Core

Methods

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

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

toConstr :: Mutez -> Constr #

dataTypeOf :: Mutez -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Mutez 
Instance details

Defined in Tezos.Core

Methods

compare :: Mutez -> Mutez -> Ordering #

(<) :: Mutez -> Mutez -> Bool #

(<=) :: Mutez -> Mutez -> Bool #

(>) :: Mutez -> Mutez -> Bool #

(>=) :: Mutez -> Mutez -> Bool #

max :: Mutez -> Mutez -> Mutez #

min :: Mutez -> Mutez -> Mutez #

Show Mutez 
Instance details

Defined in Tezos.Core

Methods

showsPrec :: Int -> Mutez -> ShowS #

show :: Mutez -> String #

showList :: [Mutez] -> ShowS #

Generic Mutez 
Instance details

Defined in Tezos.Core

Associated Types

type Rep Mutez :: Type -> Type #

Methods

from :: Mutez -> Rep Mutez x #

to :: Rep Mutez x -> Mutez #

ToJSON Mutez 
Instance details

Defined in Tezos.Core

FromJSON Mutez 
Instance details

Defined in Tezos.Core

NFData Mutez 
Instance details

Defined in Tezos.Core

Methods

rnf :: Mutez -> () #

Buildable Mutez 
Instance details

Defined in Tezos.Core

Methods

build :: Mutez -> Builder #

HasCLReader Mutez 
Instance details

Defined in Tezos.Core

TypeHasDoc Mutez 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions Mutez :: FieldDescriptions #

IsoValue Mutez 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Mutez :: T #

HasAnnotation Mutez Source # 
Instance details

Defined in Lorentz.Annotation

EDivOpHs Mutez Natural Source # 
Instance details

Defined in Lorentz.Polymorphic

EDivOpHs Mutez Mutez Source # 
Instance details

Defined in Lorentz.Polymorphic

ArithOpHs Add Mutez Mutez Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Mutez Mutez Source #

ArithOpHs Mul Natural Mutez Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Natural Mutez Source #

ArithOpHs Mul Mutez Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Mutez Natural Source #

ArithOpHs Sub Mutez Mutez Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Sub Mutez Mutez Source #

type Rep Mutez 
Instance details

Defined in Tezos.Core

type Rep Mutez = D1 ('MetaData "Mutez" "Tezos.Core" "morley-1.14.0-inplace" 'True) (C1 ('MetaCons "Mutez" 'PrefixI 'True) (S1 ('MetaSel ('Just "unMutez") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)))
type TypeDocFieldDescriptions Mutez 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type ToT Mutez 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT Mutez = 'TMutez
type EDivOpResHs Mutez Natural Source # 
Instance details

Defined in Lorentz.Polymorphic

type EDivOpResHs Mutez Mutez Source # 
Instance details

Defined in Lorentz.Polymorphic

type EModOpResHs Mutez Natural Source # 
Instance details

Defined in Lorentz.Polymorphic

type EModOpResHs Mutez Mutez Source # 
Instance details

Defined in Lorentz.Polymorphic

type ArithResHs Add Mutez Mutez Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Mul Natural Mutez Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Mul Mutez Natural Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Sub Mutez Mutez Source # 
Instance details

Defined in Lorentz.Arith

data Never Source #

Instances

Instances details
Eq Never Source # 
Instance details

Defined in Lorentz.Value

Methods

(==) :: Never -> Never -> Bool #

(/=) :: Never -> Never -> Bool #

Ord Never Source # 
Instance details

Defined in Lorentz.Value

Methods

compare :: Never -> Never -> Ordering #

(<) :: Never -> Never -> Bool #

(<=) :: Never -> Never -> Bool #

(>) :: Never -> Never -> Bool #

(>=) :: Never -> Never -> Bool #

max :: Never -> Never -> Never #

min :: Never -> Never -> Never #

Show Never Source # 
Instance details

Defined in Lorentz.Value

Methods

showsPrec :: Int -> Never -> ShowS #

show :: Never -> String #

showList :: [Never] -> ShowS #

Generic Never Source # 
Instance details

Defined in Lorentz.Value

Associated Types

type Rep Never :: Type -> Type #

Methods

from :: Never -> Rep Never x #

to :: Rep Never x -> Never #

NFData Never Source # 
Instance details

Defined in Lorentz.Value

Methods

rnf :: Never -> () #

Buildable Never Source # 
Instance details

Defined in Lorentz.Value

Methods

build :: Never -> Builder #

TypeHasDoc Never Source # 
Instance details

Defined in Lorentz.Value

Associated Types

type TypeDocFieldDescriptions Never :: FieldDescriptions #

IsoValue Never Source # 
Instance details

Defined in Lorentz.Value

Associated Types

type ToT Never :: T #

HasAnnotation Never Source # 
Instance details

Defined in Lorentz.Value

type Rep Never Source # 
Instance details

Defined in Lorentz.Value

type Rep Never = D1 ('MetaData "Never" "Lorentz.Value" "lorentz-0.11.0-inplace" 'False) (V1 :: Type -> Type)
type TypeDocFieldDescriptions Never Source # 
Instance details

Defined in Lorentz.Value

type ToT Never Source # 
Instance details

Defined in Lorentz.Value

type ToT Never = GValueType (Rep Never)

data Timestamp #

Instances

Instances details
Eq Timestamp 
Instance details

Defined in Tezos.Core

Data Timestamp 
Instance details

Defined in Tezos.Core

Methods

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

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

toConstr :: Timestamp -> Constr #

dataTypeOf :: Timestamp -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Timestamp 
Instance details

Defined in Tezos.Core

Show Timestamp 
Instance details

Defined in Tezos.Core

Generic Timestamp 
Instance details

Defined in Tezos.Core

Associated Types

type Rep Timestamp :: Type -> Type #

ToJSON Timestamp 
Instance details

Defined in Tezos.Core

FromJSON Timestamp 
Instance details

Defined in Tezos.Core

NFData Timestamp 
Instance details

Defined in Tezos.Core

Methods

rnf :: Timestamp -> () #

Buildable Timestamp 
Instance details

Defined in Tezos.Core

Methods

build :: Timestamp -> Builder #

TypeHasDoc Timestamp 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions Timestamp :: FieldDescriptions #

IsoValue Timestamp 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Timestamp :: T #

HasAnnotation Timestamp Source # 
Instance details

Defined in Lorentz.Annotation

ArithOpHs Add Integer Timestamp Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Integer Timestamp Source #

ArithOpHs Add Timestamp Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Timestamp Integer Source #

ArithOpHs Sub Timestamp Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Sub Timestamp Integer Source #

ArithOpHs Sub Timestamp Timestamp Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Sub Timestamp Timestamp Source #

type Rep Timestamp 
Instance details

Defined in Tezos.Core

type Rep Timestamp = D1 ('MetaData "Timestamp" "Tezos.Core" "morley-1.14.0-inplace" 'True) (C1 ('MetaCons "Timestamp" 'PrefixI 'True) (S1 ('MetaSel ('Just "unTimestamp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 POSIXTime)))
type TypeDocFieldDescriptions Timestamp 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type ToT Timestamp 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT Timestamp = 'TTimestamp
type ArithResHs Add Integer Timestamp Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Add Timestamp Integer Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Sub Timestamp Integer Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Sub Timestamp Timestamp Source # 
Instance details

Defined in Lorentz.Arith

data ChainId #

Instances

Instances details
Eq ChainId 
Instance details

Defined in Tezos.Core

Methods

(==) :: ChainId -> ChainId -> Bool #

(/=) :: ChainId -> ChainId -> Bool #

Ord ChainId 
Instance details

Defined in Tezos.Core

Show ChainId 
Instance details

Defined in Tezos.Core

Generic ChainId 
Instance details

Defined in Tezos.Core

Associated Types

type Rep ChainId :: Type -> Type #

Methods

from :: ChainId -> Rep ChainId x #

to :: Rep ChainId x -> ChainId #

ToJSON ChainId 
Instance details

Defined in Tezos.Core

FromJSON ChainId 
Instance details

Defined in Tezos.Core

NFData ChainId 
Instance details

Defined in Tezos.Core

Methods

rnf :: ChainId -> () #

Buildable ChainId 
Instance details

Defined in Tezos.Core

Methods

build :: ChainId -> Builder #

TypeHasDoc ChainId 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions ChainId :: FieldDescriptions #

IsoValue ChainId 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT ChainId :: T #

HasAnnotation ChainId Source # 
Instance details

Defined in Lorentz.Annotation

type Rep ChainId 
Instance details

Defined in Tezos.Core

type Rep ChainId = D1 ('MetaData "ChainId" "Tezos.Core" "morley-1.14.0-inplace" 'True) (C1 ('MetaCons "ChainIdUnsafe" 'PrefixI 'True) (S1 ('MetaSel ('Just "unChainId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))
type TypeDocFieldDescriptions ChainId 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type ToT ChainId 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT ChainId = 'TChainId

data KeyHash #

Instances

Instances details
Eq KeyHash 
Instance details

Defined in Tezos.Crypto

Methods

(==) :: KeyHash -> KeyHash -> Bool #

(/=) :: KeyHash -> KeyHash -> Bool #

Ord KeyHash 
Instance details

Defined in Tezos.Crypto

Show KeyHash 
Instance details

Defined in Tezos.Crypto

Generic KeyHash 
Instance details

Defined in Tezos.Crypto

Associated Types

type Rep KeyHash :: Type -> Type #

Methods

from :: KeyHash -> Rep KeyHash x #

to :: Rep KeyHash x -> KeyHash #

ToJSON KeyHash 
Instance details

Defined in Tezos.Crypto

ToJSONKey KeyHash 
Instance details

Defined in Tezos.Crypto

FromJSON KeyHash 
Instance details

Defined in Tezos.Crypto

FromJSONKey KeyHash 
Instance details

Defined in Tezos.Crypto

NFData KeyHash 
Instance details

Defined in Tezos.Crypto

Methods

rnf :: KeyHash -> () #

Buildable KeyHash 
Instance details

Defined in Tezos.Crypto

Methods

build :: KeyHash -> Builder #

HasCLReader KeyHash 
Instance details

Defined in Tezos.Crypto

TypeHasDoc KeyHash 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions KeyHash :: FieldDescriptions #

IsoValue KeyHash 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT KeyHash :: T #

HasAnnotation KeyHash Source # 
Instance details

Defined in Lorentz.Annotation

type Rep KeyHash 
Instance details

Defined in Tezos.Crypto

type Rep KeyHash = D1 ('MetaData "KeyHash" "Tezos.Crypto" "morley-1.14.0-inplace" 'False) (C1 ('MetaCons "KeyHash" 'PrefixI 'True) (S1 ('MetaSel ('Just "khTag") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 KeyHashTag) :*: S1 ('MetaSel ('Just "khBytes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ByteString)))
type TypeDocFieldDescriptions KeyHash 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type ToT KeyHash 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT KeyHash = 'TKeyHash

data PublicKey #

Instances

Instances details
Eq PublicKey 
Instance details

Defined in Tezos.Crypto

Ord PublicKey 
Instance details

Defined in Tezos.Crypto

Show PublicKey 
Instance details

Defined in Tezos.Crypto

Generic PublicKey 
Instance details

Defined in Tezos.Crypto

Associated Types

type Rep PublicKey :: Type -> Type #

ToJSON PublicKey 
Instance details

Defined in Tezos.Crypto

FromJSON PublicKey 
Instance details

Defined in Tezos.Crypto

NFData PublicKey 
Instance details

Defined in Tezos.Crypto

Methods

rnf :: PublicKey -> () #

Buildable PublicKey 
Instance details

Defined in Tezos.Crypto

Methods

build :: PublicKey -> Builder #

TypeHasDoc PublicKey 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions PublicKey :: FieldDescriptions #

IsoValue PublicKey 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT PublicKey :: T #

HasAnnotation PublicKey Source # 
Instance details

Defined in Lorentz.Annotation

type Rep PublicKey 
Instance details

Defined in Tezos.Crypto

type Rep PublicKey = D1 ('MetaData "PublicKey" "Tezos.Crypto" "morley-1.14.0-inplace" 'False) (C1 ('MetaCons "PublicKeyEd25519" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedUnpack) (Rec0 PublicKey)) :+: (C1 ('MetaCons "PublicKeySecp256k1" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 PublicKey)) :+: C1 ('MetaCons "PublicKeyP256" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 PublicKey))))
type TypeDocFieldDescriptions PublicKey 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type ToT PublicKey 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT PublicKey = 'TKey

data Signature #

Instances

Instances details
Eq Signature 
Instance details

Defined in Tezos.Crypto

Ord Signature 
Instance details

Defined in Tezos.Crypto

Show Signature 
Instance details

Defined in Tezos.Crypto

Generic Signature 
Instance details

Defined in Tezos.Crypto

Associated Types

type Rep Signature :: Type -> Type #

ToJSON Signature 
Instance details

Defined in Tezos.Crypto

FromJSON Signature 
Instance details

Defined in Tezos.Crypto

NFData Signature 
Instance details

Defined in Tezos.Crypto

Methods

rnf :: Signature -> () #

Buildable Signature 
Instance details

Defined in Tezos.Crypto

Methods

build :: Signature -> Builder #

TypeHasDoc Signature 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions Signature :: FieldDescriptions #

IsoValue Signature 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Signature :: T #

HasAnnotation Signature Source # 
Instance details

Defined in Lorentz.Annotation

type Rep Signature 
Instance details

Defined in Tezos.Crypto

type Rep Signature = D1 ('MetaData "Signature" "Tezos.Crypto" "morley-1.14.0-inplace" 'False) ((C1 ('MetaCons "SignatureEd25519" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedUnpack) (Rec0 Signature)) :+: C1 ('MetaCons "SignatureSecp256k1" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Signature))) :+: (C1 ('MetaCons "SignatureP256" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Signature)) :+: C1 ('MetaCons "SignatureGeneric" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ByteString))))
type TypeDocFieldDescriptions Signature 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type ToT Signature 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT Signature = 'TSignature

data Bls12381Fr #

Instances

Instances details
Bounded Bls12381Fr 
Instance details

Defined in Tezos.Crypto.BLS12381

Enum Bls12381Fr 
Instance details

Defined in Tezos.Crypto.BLS12381

Eq Bls12381Fr 
Instance details

Defined in Tezos.Crypto.BLS12381

Fractional Bls12381Fr 
Instance details

Defined in Tezos.Crypto.BLS12381

Integral Bls12381Fr 
Instance details

Defined in Tezos.Crypto.BLS12381

Num Bls12381Fr 
Instance details

Defined in Tezos.Crypto.BLS12381

Ord Bls12381Fr 
Instance details

Defined in Tezos.Crypto.BLS12381

Real Bls12381Fr 
Instance details

Defined in Tezos.Crypto.BLS12381

Show Bls12381Fr 
Instance details

Defined in Tezos.Crypto.BLS12381

NFData Bls12381Fr 
Instance details

Defined in Tezos.Crypto.BLS12381

Methods

rnf :: Bls12381Fr -> () #

IsoValue Bls12381Fr 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Bls12381Fr :: T #

CurveObject Bls12381Fr 
Instance details

Defined in Tezos.Crypto.BLS12381

ToIntegerArithOpHs Bls12381Fr Source # 
Instance details

Defined in Lorentz.Arith

MultiplyPoint Bls12381Fr Bls12381G1 
Instance details

Defined in Tezos.Crypto.BLS12381

MultiplyPoint Bls12381Fr Bls12381G2 
Instance details

Defined in Tezos.Crypto.BLS12381

UnaryArithOpHs Neg Bls12381Fr Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Neg Bls12381Fr Source #

ArithOpHs Add Bls12381Fr Bls12381Fr Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Bls12381Fr Bls12381Fr Source #

ArithOpHs Mul Integer Bls12381Fr Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Integer Bls12381Fr Source #

ArithOpHs Mul Natural Bls12381Fr Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Natural Bls12381Fr Source #

ArithOpHs Mul Bls12381Fr Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Bls12381Fr Integer Source #

ArithOpHs Mul Bls12381Fr Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Bls12381Fr Natural Source #

ArithOpHs Mul Bls12381Fr Bls12381Fr Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Bls12381Fr Bls12381Fr Source #

(Bls12381MulBadOrder Bls12381Fr Bls12381G1 :: Constraint) => ArithOpHs Mul Bls12381Fr Bls12381G1 Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Bls12381Fr Bls12381G1 Source #

(Bls12381MulBadOrder Bls12381Fr Bls12381G2 :: Constraint) => ArithOpHs Mul Bls12381Fr Bls12381G2 Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Bls12381Fr Bls12381G2 Source #

ArithOpHs Mul Bls12381G1 Bls12381Fr Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Bls12381G1 Bls12381Fr Source #

ArithOpHs Mul Bls12381G2 Bls12381Fr Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Bls12381G2 Bls12381Fr Source #

type ToT Bls12381Fr 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT Bls12381Fr = 'TBls12381Fr
type UnaryArithResHs Neg Bls12381Fr Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Add Bls12381Fr Bls12381Fr Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Mul Integer Bls12381Fr Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Mul Natural Bls12381Fr Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Mul Bls12381Fr Integer Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Mul Bls12381Fr Natural Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Mul Bls12381Fr Bls12381Fr Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Mul Bls12381Fr Bls12381G1 Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Mul Bls12381Fr Bls12381G2 Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Mul Bls12381G1 Bls12381Fr Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Mul Bls12381G2 Bls12381Fr Source # 
Instance details

Defined in Lorentz.Arith

data Bls12381G1 #

Instances

Instances details
Eq Bls12381G1 
Instance details

Defined in Tezos.Crypto.BLS12381

Show Bls12381G1 
Instance details

Defined in Tezos.Crypto.BLS12381

NFData Bls12381G1 
Instance details

Defined in Tezos.Crypto.BLS12381

Methods

rnf :: Bls12381G1 -> () #

IsoValue Bls12381G1 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Bls12381G1 :: T #

CurveObject Bls12381G1 
Instance details

Defined in Tezos.Crypto.BLS12381

MultiplyPoint Integer Bls12381G1 
Instance details

Defined in Tezos.Crypto.BLS12381

MultiplyPoint Bls12381Fr Bls12381G1 
Instance details

Defined in Tezos.Crypto.BLS12381

UnaryArithOpHs Neg Bls12381G1 Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Neg Bls12381G1 Source #

ArithOpHs Add Bls12381G1 Bls12381G1 Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Bls12381G1 Bls12381G1 Source #

(Bls12381MulBadOrder Bls12381Fr Bls12381G1 :: Constraint) => ArithOpHs Mul Bls12381Fr Bls12381G1 Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Bls12381Fr Bls12381G1 Source #

ArithOpHs Mul Bls12381G1 Bls12381Fr Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Bls12381G1 Bls12381Fr Source #

type ToT Bls12381G1 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT Bls12381G1 = 'TBls12381G1
type UnaryArithResHs Neg Bls12381G1 Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Add Bls12381G1 Bls12381G1 Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Mul Bls12381Fr Bls12381G1 Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Mul Bls12381G1 Bls12381Fr Source # 
Instance details

Defined in Lorentz.Arith

data Bls12381G2 #

Instances

Instances details
Eq Bls12381G2 
Instance details

Defined in Tezos.Crypto.BLS12381

Show Bls12381G2 
Instance details

Defined in Tezos.Crypto.BLS12381

NFData Bls12381G2 
Instance details

Defined in Tezos.Crypto.BLS12381

Methods

rnf :: Bls12381G2 -> () #

IsoValue Bls12381G2 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Bls12381G2 :: T #

CurveObject Bls12381G2 
Instance details

Defined in Tezos.Crypto.BLS12381

MultiplyPoint Integer Bls12381G2 
Instance details

Defined in Tezos.Crypto.BLS12381

MultiplyPoint Bls12381Fr Bls12381G2 
Instance details

Defined in Tezos.Crypto.BLS12381

UnaryArithOpHs Neg Bls12381G2 Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Neg Bls12381G2 Source #

ArithOpHs Add Bls12381G2 Bls12381G2 Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Bls12381G2 Bls12381G2 Source #

(Bls12381MulBadOrder Bls12381Fr Bls12381G2 :: Constraint) => ArithOpHs Mul Bls12381Fr Bls12381G2 Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Bls12381Fr Bls12381G2 Source #

ArithOpHs Mul Bls12381G2 Bls12381Fr Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Bls12381G2 Bls12381Fr Source #

type ToT Bls12381G2 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT Bls12381G2 = 'TBls12381G2
type UnaryArithResHs Neg Bls12381G2 Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Add Bls12381G2 Bls12381G2 Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Mul Bls12381Fr Bls12381G2 Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Mul Bls12381G2 Bls12381Fr Source # 
Instance details

Defined in Lorentz.Arith

data Set a #

A set of values a.

Instances

Instances details
Foldable Set

Folds in order of increasing key.

Instance details

Defined in Data.Set.Internal

Methods

fold :: Monoid m => Set m -> m #

foldMap :: Monoid m => (a -> m) -> Set a -> m #

foldMap' :: Monoid m => (a -> m) -> Set a -> m #

foldr :: (a -> b -> b) -> b -> Set a -> b #

foldr' :: (a -> b -> b) -> b -> Set a -> b #

foldl :: (b -> a -> b) -> b -> Set a -> b #

foldl' :: (b -> a -> b) -> b -> Set a -> b #

foldr1 :: (a -> a -> a) -> Set a -> a #

foldl1 :: (a -> a -> a) -> Set a -> a #

toList :: Set a -> [a] #

null :: Set a -> Bool #

length :: Set a -> Int #

elem :: Eq a => a -> Set a -> Bool #

maximum :: Ord a => Set a -> a #

minimum :: Ord a => Set a -> a #

sum :: Num a => Set a -> a #

product :: Num a => Set a -> a #

ToJSON1 Set 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Set a -> Value #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Set a] -> Value #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Set a -> Encoding #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Set a] -> Encoding #

Eq1 Set

Since: containers-0.5.9

Instance details

Defined in Data.Set.Internal

Methods

liftEq :: (a -> b -> Bool) -> Set a -> Set b -> Bool #

Ord1 Set

Since: containers-0.5.9

Instance details

Defined in Data.Set.Internal

Methods

liftCompare :: (a -> b -> Ordering) -> Set a -> Set b -> Ordering #

Show1 Set

Since: containers-0.5.9

Instance details

Defined in Data.Set.Internal

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Set a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Set a] -> ShowS #

Ord a => IsList (Set a)

Since: containers-0.5.6.2

Instance details

Defined in Data.Set.Internal

Associated Types

type Item (Set a) #

Methods

fromList :: [Item (Set a)] -> Set a #

fromListN :: Int -> [Item (Set a)] -> Set a #

toList :: Set a -> [Item (Set a)] #

Eq a => Eq (Set a) 
Instance details

Defined in Data.Set.Internal

Methods

(==) :: Set a -> Set a -> Bool #

(/=) :: Set a -> Set a -> Bool #

(Data a, Ord a) => Data (Set a) 
Instance details

Defined in Data.Set.Internal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Set a -> c (Set a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Set a) #

toConstr :: Set a -> Constr #

dataTypeOf :: Set a -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> Set a -> Set a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Set a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Set a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Set a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Set a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Set a -> m (Set a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Set a -> m (Set a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Set a -> m (Set a) #

Ord a => Ord (Set a) 
Instance details

Defined in Data.Set.Internal

Methods

compare :: Set a -> Set a -> Ordering #

(<) :: Set a -> Set a -> Bool #

(<=) :: Set a -> Set a -> Bool #

(>) :: Set a -> Set a -> Bool #

(>=) :: Set a -> Set a -> Bool #

max :: Set a -> Set a -> Set a #

min :: Set a -> Set a -> Set a #

(Read a, Ord a) => Read (Set a) 
Instance details

Defined in Data.Set.Internal

Show a => Show (Set a) 
Instance details

Defined in Data.Set.Internal

Methods

showsPrec :: Int -> Set a -> ShowS #

show :: Set a -> String #

showList :: [Set a] -> ShowS #

Ord a => Semigroup (Set a)

Since: containers-0.5.7

Instance details

Defined in Data.Set.Internal

Methods

(<>) :: Set a -> Set a -> Set a #

sconcat :: NonEmpty (Set a) -> Set a #

stimes :: Integral b => b -> Set a -> Set a #

Ord a => Monoid (Set a) 
Instance details

Defined in Data.Set.Internal

Methods

mempty :: Set a #

mappend :: Set a -> Set a -> Set a #

mconcat :: [Set a] -> Set a #

ToJSON a => ToJSON (Set a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Set a -> Value #

toEncoding :: Set a -> Encoding #

toJSONList :: [Set a] -> Value #

toEncodingList :: [Set a] -> Encoding #

NFData a => NFData (Set a) 
Instance details

Defined in Data.Set.Internal

Methods

rnf :: Set a -> () #

Ord a => Contains (Set a) 
Instance details

Defined in Control.Lens.At

Methods

contains :: Index (Set a) -> Lens' (Set a) Bool #

Ord k => Ixed (Set k) 
Instance details

Defined in Control.Lens.At

Methods

ix :: Index (Set k) -> Traversal' (Set k) (IxValue (Set k)) #

Ord k => At (Set k) 
Instance details

Defined in Control.Lens.At

Methods

at :: Index (Set k) -> Lens' (Set k) (Maybe (IxValue (Set k))) #

Ord a => Wrapped (Set a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Set a) #

Methods

_Wrapped' :: Iso' (Set a) (Unwrapped (Set a)) #

(Ord a, Monoid a) => Semiring (Set a)

The multiplication laws are satisfied for any underlying Monoid, so we require a Monoid constraint instead of a Semiring constraint since times can use the context of either.

Instance details

Defined in Data.Semiring

Methods

plus :: Set a -> Set a -> Set a #

zero :: Set a #

times :: Set a -> Set a -> Set a #

one :: Set a #

fromNatural :: Natural -> Set a #

Ord v => Container (Set v) 
Instance details

Defined in Universum.Container.Class

Associated Types

type Element (Set v) #

Methods

toList :: Set v -> [Element (Set v)] #

null :: Set v -> Bool #

foldr :: (Element (Set v) -> b -> b) -> b -> Set v -> b #

foldl :: (b -> Element (Set v) -> b) -> b -> Set v -> b #

foldl' :: (b -> Element (Set v) -> b) -> b -> Set v -> b #

length :: Set v -> Int #

elem :: Element (Set v) -> Set v -> Bool #

maximum :: Set v -> Element (Set v) #

minimum :: Set v -> Element (Set v) #

foldMap :: Monoid m => (Element (Set v) -> m) -> Set v -> m #

fold :: Set v -> Element (Set v) #

foldr' :: (Element (Set v) -> b -> b) -> b -> Set v -> b #

foldr1 :: (Element (Set v) -> Element (Set v) -> Element (Set v)) -> Set v -> Element (Set v) #

foldl1 :: (Element (Set v) -> Element (Set v) -> Element (Set v)) -> Set v -> Element (Set v) #

notElem :: Element (Set v) -> Set v -> Bool #

all :: (Element (Set v) -> Bool) -> Set v -> Bool #

any :: (Element (Set v) -> Bool) -> Set v -> Bool #

and :: Set v -> Bool #

or :: Set v -> Bool #

find :: (Element (Set v) -> Bool) -> Set v -> Maybe (Element (Set v)) #

safeHead :: Set v -> Maybe (Element (Set v)) #

One (Set v) 
Instance details

Defined in Universum.Container.Class

Associated Types

type OneItem (Set v) #

Methods

one :: OneItem (Set v) -> Set v #

PolyCTypeHasDocC '[a] => TypeHasDoc (Set a) 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions (Set a) :: FieldDescriptions #

Methods

typeDocName :: Proxy (Set a) -> Text #

typeDocMdDescription :: Markdown #

typeDocMdReference :: Proxy (Set a) -> WithinParens -> Markdown #

typeDocDependencies :: Proxy (Set a) -> [SomeDocDefinitionItem] #

typeDocHaskellRep :: TypeDocHaskellRep (Set a) #

typeDocMichelsonRep :: TypeDocMichelsonRep (Set a) #

(Comparable (ToT c), Ord c, IsoValue c) => IsoValue (Set c) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (Set c) :: T #

Methods

toVal :: Set c -> Value (ToT (Set c)) #

fromVal :: Value (ToT (Set c)) -> Set c #

KnownIsoT v => HasAnnotation (Set v) Source # 
Instance details

Defined in Lorentz.Annotation

NiceComparable a => UpdOpHs (Set a) Source # 
Instance details

Defined in Lorentz.Polymorphic

Associated Types

type UpdOpKeyHs (Set a) Source #

type UpdOpParamsHs (Set a) Source #

SizeOpHs (Set a) Source # 
Instance details

Defined in Lorentz.Polymorphic

NiceComparable e => IterOpHs (Set e) Source # 
Instance details

Defined in Lorentz.Polymorphic

Associated Types

type IterOpElHs (Set e) Source #

NiceComparable e => MemOpHs (Set e) Source # 
Instance details

Defined in Lorentz.Polymorphic

Associated Types

type MemOpKeyHs (Set e) Source #

LDefault (Set k) Source # 
Instance details

Defined in Lorentz.Default

Methods

ldef :: Set k Source #

lIsDef :: forall (s :: [Type]). (Set k ': s) :-> (Bool ': s) Source #

(t ~ Set a', Ord a) => Rewrapped (Set a) t

Use wrapping fromList. unwrapping returns a sorted list.

Instance details

Defined in Control.Lens.Wrapped

CanCastTo k1 k2 => CanCastTo (Set k1 :: Type) (Set k2 :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (Set k1) -> Proxy (Set k2) -> () Source #

NiceComparable key => StoreHasSubmap (Set key) SelfRef key () Source # 
Instance details

Defined in Lorentz.StoreClass

type Item (Set a) 
Instance details

Defined in Data.Set.Internal

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

Defined in Control.Lens.At

type Index (Set a) = a
type IxValue (Set k) 
Instance details

Defined in Control.Lens.At

type IxValue (Set k) = ()
type Unwrapped (Set a) 
Instance details

Defined in Control.Lens.Wrapped

type Unwrapped (Set a) = [a]
type Element (Set v) 
Instance details

Defined in Universum.Container.Class

type Element (Set v) = ElementDefault (Set v)
type OneItem (Set v) 
Instance details

Defined in Universum.Container.Class

type OneItem (Set v) = v
type TypeDocFieldDescriptions (Set a) 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type ToT (Set c) 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT (Set c) = 'TSet (ToT c)
type UpdOpKeyHs (Set a) Source # 
Instance details

Defined in Lorentz.Polymorphic

type UpdOpKeyHs (Set a) = a
type UpdOpParamsHs (Set a) Source # 
Instance details

Defined in Lorentz.Polymorphic

type IterOpElHs (Set e) Source # 
Instance details

Defined in Lorentz.Polymorphic

type IterOpElHs (Set e) = e
type MemOpKeyHs (Set e) Source # 
Instance details

Defined in Lorentz.Polymorphic

type MemOpKeyHs (Set e) = e

data Map k a #

A Map from keys k to values a.

The Semigroup operation for Map is union, which prefers values from the left operand. If m1 maps a key k to a value a1, and m2 maps the same key to a different value a2, then their union m1 <> m2 maps k to a1.

Instances

Instances details
Eq2 Map

Since: containers-0.5.9

Instance details

Defined in Data.Map.Internal

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> Map a c -> Map b d -> Bool #

Ord2 Map

Since: containers-0.5.9

Instance details

Defined in Data.Map.Internal

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> Map a c -> Map b d -> Ordering #

Show2 Map

Since: containers-0.5.9

Instance details

Defined in Data.Map.Internal

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> Map a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [Map a b] -> ShowS #

Functor (Map k) 
Instance details

Defined in Data.Map.Internal

Methods

fmap :: (a -> b) -> Map k a -> Map k b #

(<$) :: a -> Map k b -> Map k a #

Foldable (Map k)

Folds in order of increasing key.

Instance details

Defined in Data.Map.Internal

Methods

fold :: Monoid m => Map k m -> m #

foldMap :: Monoid m => (a -> m) -> Map k a -> m #

foldMap' :: Monoid m => (a -> m) -> Map k a -> m #

foldr :: (a -> b -> b) -> b -> Map k a -> b #

foldr' :: (a -> b -> b) -> b -> Map k a -> b #

foldl :: (b -> a -> b) -> b -> Map k a -> b #

foldl' :: (b -> a -> b) -> b -> Map k a -> b #

foldr1 :: (a -> a -> a) -> Map k a -> a #

foldl1 :: (a -> a -> a) -> Map k a -> a #

toList :: Map k a -> [a] #

null :: Map k a -> Bool #

length :: Map k a -> Int #

elem :: Eq a => a -> Map k a -> Bool #

maximum :: Ord a => Map k a -> a #

minimum :: Ord a => Map k a -> a #

sum :: Num a => Map k a -> a #

product :: Num a => Map k a -> a #

Traversable (Map k)

Traverses in order of increasing key.

Instance details

Defined in Data.Map.Internal

Methods

traverse :: Applicative f => (a -> f b) -> Map k a -> f (Map k b) #

sequenceA :: Applicative f => Map k (f a) -> f (Map k a) #

mapM :: Monad m => (a -> m b) -> Map k a -> m (Map k b) #

sequence :: Monad m => Map k (m a) -> m (Map k a) #

ToJSONKey k => ToJSON1 (Map k) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Map k a -> Value #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Map k a] -> Value #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Map k a -> Encoding #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Map k a] -> Encoding #

Eq k => Eq1 (Map k)

Since: containers-0.5.9

Instance details

Defined in Data.Map.Internal

Methods

liftEq :: (a -> b -> Bool) -> Map k a -> Map k b -> Bool #

Ord k => Ord1 (Map k)

Since: containers-0.5.9

Instance details

Defined in Data.Map.Internal

Methods

liftCompare :: (a -> b -> Ordering) -> Map k a -> Map k b -> Ordering #

(Ord k, Read k) => Read1 (Map k)

Since: containers-0.5.9

Instance details

Defined in Data.Map.Internal

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Map k a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Map k a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Map k a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Map k a] #

Show k => Show1 (Map k)

Since: containers-0.5.9

Instance details

Defined in Data.Map.Internal

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Map k a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Map k a] -> ShowS #

(CanCastTo k1 k2, CanCastTo v1 v2) => CanCastTo (Map k1 v1 :: Type) (Map k2 v2 :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (Map k1 v1) -> Proxy (Map k2 v2) -> () Source #

Ord k => IsList (Map k v)

Since: containers-0.5.6.2

Instance details

Defined in Data.Map.Internal

Associated Types

type Item (Map k v) #

Methods

fromList :: [Item (Map k v)] -> Map k v #

fromListN :: Int -> [Item (Map k v)] -> Map k v #

toList :: Map k v -> [Item (Map k v)] #

(Eq k, Eq a) => Eq (Map k a) 
Instance details

Defined in Data.Map.Internal

Methods

(==) :: Map k a -> Map k a -> Bool #

(/=) :: Map k a -> Map k a -> Bool #

(Data k, Data a, Ord k) => Data (Map k a) 
Instance details

Defined in Data.Map.Internal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Map k a -> c (Map k a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Map k a) #

toConstr :: Map k a -> Constr #

dataTypeOf :: Map k a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Map k a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Map k a)) #

gmapT :: (forall b. Data b => b -> b) -> Map k a -> Map k a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Map k a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Map k a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Map k a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Map k a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Map k a -> m (Map k a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Map k a -> m (Map k a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Map k a -> m (Map k a) #

(Ord k, Ord v) => Ord (Map k v) 
Instance details

Defined in Data.Map.Internal

Methods

compare :: Map k v -> Map k v -> Ordering #

(<) :: Map k v -> Map k v -> Bool #

(<=) :: Map k v -> Map k v -> Bool #

(>) :: Map k v -> Map k v -> Bool #

(>=) :: Map k v -> Map k v -> Bool #

max :: Map k v -> Map k v -> Map k v #

min :: Map k v -> Map k v -> Map k v #

(Ord k, Read k, Read e) => Read (Map k e) 
Instance details

Defined in Data.Map.Internal

Methods

readsPrec :: Int -> ReadS (Map k e) #

readList :: ReadS [Map k e] #

readPrec :: ReadPrec (Map k e) #

readListPrec :: ReadPrec [Map k e] #

(Show k, Show a) => Show (Map k a) 
Instance details

Defined in Data.Map.Internal

Methods

showsPrec :: Int -> Map k a -> ShowS #

show :: Map k a -> String #

showList :: [Map k a] -> ShowS #

Ord k => Semigroup (Map k v) 
Instance details

Defined in Data.Map.Internal

Methods

(<>) :: Map k v -> Map k v -> Map k v #

sconcat :: NonEmpty (Map k v) -> Map k v #

stimes :: Integral b => b -> Map k v -> Map k v #

Ord k => Monoid (Map k v) 
Instance details

Defined in Data.Map.Internal

Methods

mempty :: Map k v #

mappend :: Map k v -> Map k v -> Map k v #

mconcat :: [Map k v] -> Map k v #

(ToJSON v, ToJSONKey k) => ToJSON (Map k v) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Map k v -> Value #

toEncoding :: Map k v -> Encoding #

toJSONList :: [Map k v] -> Value #

toEncodingList :: [Map k v] -> Encoding #

(NFData k, NFData a) => NFData (Map k a) 
Instance details

Defined in Data.Map.Internal

Methods

rnf :: Map k a -> () #

Ord k => Ixed (Map k a) 
Instance details

Defined in Control.Lens.At

Methods

ix :: Index (Map k a) -> Traversal' (Map k a) (IxValue (Map k a)) #

Ord k => At (Map k a) 
Instance details

Defined in Control.Lens.At

Methods

at :: Index (Map k a) -> Lens' (Map k a) (Maybe (IxValue (Map k a))) #

Ord k => Wrapped (Map k a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Map k a) #

Methods

_Wrapped' :: Iso' (Map k a) (Unwrapped (Map k a)) #

(Ord k, Monoid k, Semiring v) => Semiring (Map k v)

The multiplication laws are satisfied for any underlying Monoid as the key type, so we require a Monoid constraint instead of a Semiring constraint since times can use the context of either.

Instance details

Defined in Data.Semiring

Methods

plus :: Map k v -> Map k v -> Map k v #

zero :: Map k v #

times :: Map k v -> Map k v -> Map k v #

one :: Map k v #

fromNatural :: Natural -> Map k v #

ToPairs (Map k v) 
Instance details

Defined in Universum.Container.Class

Associated Types

type Key (Map k v) #

type Val (Map k v) #

Methods

toPairs :: Map k v -> [(Key (Map k v), Val (Map k v))] #

keys :: Map k v -> [Key (Map k v)] #

elems :: Map k v -> [Val (Map k v)] #

Container (Map k v) 
Instance details

Defined in Universum.Container.Class

Associated Types

type Element (Map k v) #

Methods

toList :: Map k v -> [Element (Map k v)] #

null :: Map k v -> Bool #

foldr :: (Element (Map k v) -> b -> b) -> b -> Map k v -> b #

foldl :: (b -> Element (Map k v) -> b) -> b -> Map k v -> b #

foldl' :: (b -> Element (Map k v) -> b) -> b -> Map k v -> b #

length :: Map k v -> Int #

elem :: Element (Map k v) -> Map k v -> Bool #

maximum :: Map k v -> Element (Map k v) #

minimum :: Map k v -> Element (Map k v) #

foldMap :: Monoid m => (Element (Map k v) -> m) -> Map k v -> m #

fold :: Map k v -> Element (Map k v) #

foldr' :: (Element (Map k v) -> b -> b) -> b -> Map k v -> b #

foldr1 :: (Element (Map k v) -> Element (Map k v) -> Element (Map k v)) -> Map k v -> Element (Map k v) #

foldl1 :: (Element (Map k v) -> Element (Map k v) -> Element (Map k v)) -> Map k v -> Element (Map k v) #

notElem :: Element (Map k v) -> Map k v -> Bool #

all :: (Element (Map k v) -> Bool) -> Map k v -> Bool #

any :: (Element (Map k v) -> Bool) -> Map k v -> Bool #

and :: Map k v -> Bool #

or :: Map k v -> Bool #

find :: (Element (Map k v) -> Bool) -> Map k v -> Maybe (Element (Map k v)) #

safeHead :: Map k v -> Maybe (Element (Map k v)) #

One (Map k v) 
Instance details

Defined in Universum.Container.Class

Associated Types

type OneItem (Map k v) #

Methods

one :: OneItem (Map k v) -> Map k v #

(PolyCTypeHasDocC '[k], PolyTypeHasDocC '[v], Ord k) => TypeHasDoc (Map k v) 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions (Map k v) :: FieldDescriptions #

Methods

typeDocName :: Proxy (Map k v) -> Text #

typeDocMdDescription :: Markdown #

typeDocMdReference :: Proxy (Map k v) -> WithinParens -> Markdown #

typeDocDependencies :: Proxy (Map k v) -> [SomeDocDefinitionItem] #

typeDocHaskellRep :: TypeDocHaskellRep (Map k v) #

typeDocMichelsonRep :: TypeDocMichelsonRep (Map k v) #

(Comparable (ToT k), Ord k, IsoValue k, IsoValue v) => IsoValue (Map k v) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (Map k v) :: T #

Methods

toVal :: Map k v -> Value (ToT (Map k v)) #

fromVal :: Value (ToT (Map k v)) -> Map k v #

(HasAnnotation k, HasAnnotation v) => HasAnnotation (Map k v) Source # 
Instance details

Defined in Lorentz.Annotation

NiceComparable k => GetOpHs (Map k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

Associated Types

type GetOpKeyHs (Map k v) Source #

type GetOpValHs (Map k v) Source #

NiceComparable k => UpdOpHs (Map k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

Associated Types

type UpdOpKeyHs (Map k v) Source #

type UpdOpParamsHs (Map k v) Source #

SizeOpHs (Map k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

NiceComparable k => IterOpHs (Map k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

Associated Types

type IterOpElHs (Map k v) Source #

NiceComparable k => MapOpHs (Map k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

Associated Types

type MapOpInpHs (Map k v) Source #

type MapOpResHs (Map k v) :: Type -> Type Source #

NiceComparable k => MemOpHs (Map k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

Associated Types

type MemOpKeyHs (Map k v) Source #

LDefault (Map k v) Source # 
Instance details

Defined in Lorentz.Default

Methods

ldef :: Map k v Source #

lIsDef :: forall (s :: [Type]). (Map k v ': s) :-> (Bool ': s) Source #

(t ~ Map k' a', Ord k) => Rewrapped (Map k a) t

Use wrapping fromList. unwrapping returns a sorted list.

Instance details

Defined in Control.Lens.Wrapped

(NiceComparable key, KnownValue value) => StoreHasSubmap (Map key value) SelfRef key value Source # 
Instance details

Defined in Lorentz.StoreClass

Methods

storeSubmapOps :: StoreSubmapOps (Map key value) SelfRef key value Source #

type Item (Map k v) 
Instance details

Defined in Data.Map.Internal

type Item (Map k v) = (k, v)
type Index (Map k a) 
Instance details

Defined in Control.Lens.At

type Index (Map k a) = k
type IxValue (Map k a) 
Instance details

Defined in Control.Lens.At

type IxValue (Map k a) = a
type Unwrapped (Map k a) 
Instance details

Defined in Control.Lens.Wrapped

type Unwrapped (Map k a) = [(k, a)]
type Val (Map k v) 
Instance details

Defined in Universum.Container.Class

type Val (Map k v) = v
type Key (Map k v) 
Instance details

Defined in Universum.Container.Class

type Key (Map k v) = k
type Element (Map k v) 
Instance details

Defined in Universum.Container.Class

type Element (Map k v) = ElementDefault (Map k v)
type OneItem (Map k v) 
Instance details

Defined in Universum.Container.Class

type OneItem (Map k v) = (k, v)
type TypeDocFieldDescriptions (Map k v) 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type TypeDocFieldDescriptions (Map k v) = '[] :: [(Symbol, (Maybe Symbol, [(Symbol, Symbol)]))]
type ToT (Map k v) 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT (Map k v) = 'TMap (ToT k) (ToT v)
type GetOpKeyHs (Map k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

type GetOpKeyHs (Map k v) = k
type GetOpValHs (Map k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

type GetOpValHs (Map k v) = v
type UpdOpKeyHs (Map k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

type UpdOpKeyHs (Map k v) = k
type UpdOpParamsHs (Map k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

type UpdOpParamsHs (Map k v) = Maybe v
type IterOpElHs (Map k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

type IterOpElHs (Map k v) = (k, v)
type MapOpInpHs (Map k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

type MapOpInpHs (Map k v) = (k, v)
type MapOpResHs (Map k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

type MapOpResHs (Map k v) = Map k
type MemOpKeyHs (Map k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

type MemOpKeyHs (Map k v) = k

newtype BigMap k v #

Constructors

BigMap 

Fields

Instances

Instances details
(CanCastTo k1 k2, CanCastTo v1 v2) => CanCastTo (BigMap k1 v1 :: Type) (BigMap k2 v2 :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (BigMap k1 v1) -> Proxy (BigMap k2 v2) -> () Source #

Ord k => IsList (BigMap k v) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type Item (BigMap k v) #

Methods

fromList :: [Item (BigMap k v)] -> BigMap k v #

fromListN :: Int -> [Item (BigMap k v)] -> BigMap k v #

toList :: BigMap k v -> [Item (BigMap k v)] #

(Eq k, Eq v) => Eq (BigMap k v) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Methods

(==) :: BigMap k v -> BigMap k v -> Bool #

(/=) :: BigMap k v -> BigMap k v -> Bool #

(Show k, Show v) => Show (BigMap k v) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Methods

showsPrec :: Int -> BigMap k v -> ShowS #

show :: BigMap k v -> String #

showList :: [BigMap k v] -> ShowS #

Ord k => Semigroup (BigMap k v) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Methods

(<>) :: BigMap k v -> BigMap k v -> BigMap k v #

sconcat :: NonEmpty (BigMap k v) -> BigMap k v #

stimes :: Integral b => b -> BigMap k v -> BigMap k v #

Ord k => Monoid (BigMap k v) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Methods

mempty :: BigMap k v #

mappend :: BigMap k v -> BigMap k v -> BigMap k v #

mconcat :: [BigMap k v] -> BigMap k v #

Default (BigMap k v) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Methods

def :: BigMap k v #

(Ord k, Buildable k, Buildable v) => Buildable (BigMap k v) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Methods

build :: BigMap k v -> Builder #

Container (BigMap k v) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type Element (BigMap k v) #

Methods

toList :: BigMap k v -> [Element (BigMap k v)] #

null :: BigMap k v -> Bool #

foldr :: (Element (BigMap k v) -> b -> b) -> b -> BigMap k v -> b #

foldl :: (b -> Element (BigMap k v) -> b) -> b -> BigMap k v -> b #

foldl' :: (b -> Element (BigMap k v) -> b) -> b -> BigMap k v -> b #

length :: BigMap k v -> Int #

elem :: Element (BigMap k v) -> BigMap k v -> Bool #

maximum :: BigMap k v -> Element (BigMap k v) #

minimum :: BigMap k v -> Element (BigMap k v) #

foldMap :: Monoid m => (Element (BigMap k v) -> m) -> BigMap k v -> m #

fold :: BigMap k v -> Element (BigMap k v) #

foldr' :: (Element (BigMap k v) -> b -> b) -> b -> BigMap k v -> b #

foldr1 :: (Element (BigMap k v) -> Element (BigMap k v) -> Element (BigMap k v)) -> BigMap k v -> Element (BigMap k v) #

foldl1 :: (Element (BigMap k v) -> Element (BigMap k v) -> Element (BigMap k v)) -> BigMap k v -> Element (BigMap k v) #

notElem :: Element (BigMap k v) -> BigMap k v -> Bool #

all :: (Element (BigMap k v) -> Bool) -> BigMap k v -> Bool #

any :: (Element (BigMap k v) -> Bool) -> BigMap k v -> Bool #

and :: BigMap k v -> Bool #

or :: BigMap k v -> Bool #

find :: (Element (BigMap k v) -> Bool) -> BigMap k v -> Maybe (Element (BigMap k v)) #

safeHead :: BigMap k v -> Maybe (Element (BigMap k v)) #

One (BigMap k v) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type OneItem (BigMap k v) #

Methods

one :: OneItem (BigMap k v) -> BigMap k v #

(PolyCTypeHasDocC '[k], PolyTypeHasDocC '[v], Ord k) => TypeHasDoc (BigMap k v) 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions (BigMap k v) :: FieldDescriptions #

Methods

typeDocName :: Proxy (BigMap k v) -> Text #

typeDocMdDescription :: Markdown #

typeDocMdReference :: Proxy (BigMap k v) -> WithinParens -> Markdown #

typeDocDependencies :: Proxy (BigMap k v) -> [SomeDocDefinitionItem] #

typeDocHaskellRep :: TypeDocHaskellRep (BigMap k v) #

typeDocMichelsonRep :: TypeDocMichelsonRep (BigMap k v) #

(WellTypedToT k, WellTypedToT v, Comparable (ToT k), Ord k, IsoValue k, IsoValue v) => IsoValue (BigMap k v) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (BigMap k v) :: T #

Methods

toVal :: BigMap k v -> Value (ToT (BigMap k v)) #

fromVal :: Value (ToT (BigMap k v)) -> BigMap k v #

(HasAnnotation k, HasAnnotation v) => HasAnnotation (BigMap k v) Source # 
Instance details

Defined in Lorentz.Annotation

NiceComparable k => GetOpHs (BigMap k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

Associated Types

type GetOpKeyHs (BigMap k v) Source #

type GetOpValHs (BigMap k v) Source #

NiceComparable k => UpdOpHs (BigMap k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

Associated Types

type UpdOpKeyHs (BigMap k v) Source #

type UpdOpParamsHs (BigMap k v) Source #

NiceComparable k => MemOpHs (BigMap k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

Associated Types

type MemOpKeyHs (BigMap k v) Source #

(NiceComparable key, KnownValue value) => StoreHasSubmap (BigMap key value) SelfRef key value Source # 
Instance details

Defined in Lorentz.StoreClass

Methods

storeSubmapOps :: StoreSubmapOps (BigMap key value) SelfRef key value Source #

type Item (BigMap k v) 
Instance details

Defined in Michelson.Typed.Haskell.Value

type Item (BigMap k v) = Item (Map k v)
type Element (BigMap k v) 
Instance details

Defined in Michelson.Typed.Haskell.Value

type Element (BigMap k v) = Element (Map k v)
type OneItem (BigMap k v) 
Instance details

Defined in Michelson.Typed.Haskell.Value

type OneItem (BigMap k v) = OneItem (Map k v)
type TypeDocFieldDescriptions (BigMap k v) 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type ToT (BigMap k v) 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT (BigMap k v) = 'TBigMap (ToT k) (ToT v)
type GetOpKeyHs (BigMap k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

type GetOpKeyHs (BigMap k v) = k
type GetOpValHs (BigMap k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

type GetOpValHs (BigMap k v) = v
type UpdOpKeyHs (BigMap k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

type UpdOpKeyHs (BigMap k v) = k
type UpdOpParamsHs (BigMap k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

type UpdOpParamsHs (BigMap k v) = Maybe v
type MemOpKeyHs (BigMap k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

type MemOpKeyHs (BigMap k v) = k

type Operation = Operation' Instr #

data Maybe a #

The Maybe type encapsulates an optional value. A value of type Maybe a either contains a value of type a (represented as Just a), or it is empty (represented as Nothing). Using Maybe is a good way to deal with errors or exceptional cases without resorting to drastic measures such as error.

The Maybe type is also a monad. It is a simple kind of error monad, where all errors are represented by Nothing. A richer error monad can be built using the Either type.

Constructors

Nothing 
Just a 

Instances

Instances details
Monad Maybe

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

(>>=) :: Maybe a -> (a -> Maybe b) -> Maybe b #

(>>) :: Maybe a -> Maybe b -> Maybe b #

return :: a -> Maybe a #

Functor Maybe

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

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

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

MonadFail Maybe

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.Fail

Methods

fail :: String -> Maybe a #

Applicative Maybe

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

pure :: a -> Maybe a #

(<*>) :: Maybe (a -> b) -> Maybe a -> Maybe b #

liftA2 :: (a -> b -> c) -> Maybe a -> Maybe b -> Maybe c #

(*>) :: Maybe a -> Maybe b -> Maybe b #

(<*) :: Maybe a -> Maybe b -> Maybe a #

Foldable Maybe

Since: base-2.1

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => Maybe m -> m #

foldMap :: Monoid m => (a -> m) -> Maybe a -> m #

foldMap' :: Monoid m => (a -> m) -> Maybe a -> m #

foldr :: (a -> b -> b) -> b -> Maybe a -> b #

foldr' :: (a -> b -> b) -> b -> Maybe a -> b #

foldl :: (b -> a -> b) -> b -> Maybe a -> b #

foldl' :: (b -> a -> b) -> b -> Maybe a -> b #

foldr1 :: (a -> a -> a) -> Maybe a -> a #

foldl1 :: (a -> a -> a) -> Maybe a -> a #

toList :: Maybe a -> [a] #

null :: Maybe a -> Bool #

length :: Maybe a -> Int #

elem :: Eq a => a -> Maybe a -> Bool #

maximum :: Ord a => Maybe a -> a #

minimum :: Ord a => Maybe a -> a #

sum :: Num a => Maybe a -> a #

product :: Num a => Maybe a -> a #

Traversable Maybe

Since: base-2.1

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Maybe a -> f (Maybe b) #

sequenceA :: Applicative f => Maybe (f a) -> f (Maybe a) #

mapM :: Monad m => (a -> m b) -> Maybe a -> m (Maybe b) #

sequence :: Monad m => Maybe (m a) -> m (Maybe a) #

MonadPlus Maybe

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mzero :: Maybe a #

mplus :: Maybe a -> Maybe a -> Maybe a #

ToJSON1 Maybe 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Maybe a -> Value #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Maybe a] -> Value #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Maybe a -> Encoding #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Maybe a] -> Encoding #

Alternative Maybe

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

empty :: Maybe a #

(<|>) :: Maybe a -> Maybe a -> Maybe a #

some :: Maybe a -> Maybe [a] #

many :: Maybe a -> Maybe [a] #

Eq1 Maybe

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> Maybe a -> Maybe b -> Bool #

Ord1 Maybe

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a -> b -> Ordering) -> Maybe a -> Maybe b -> Ordering #

Read1 Maybe

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Maybe a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Maybe a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Maybe a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Maybe a] #

Show1 Maybe

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Maybe a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Maybe a] -> ShowS #

MonadFailure Maybe 
Instance details

Defined in Basement.Monad

Associated Types

type Failure Maybe #

Methods

mFail :: Failure Maybe -> Maybe () #

NFData1 Maybe

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> Maybe a -> () #

MonadThrow Maybe 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> Maybe a #

Hashable1 Maybe 
Instance details

Defined in Data.Hashable.Class

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Maybe a -> Int #

InjValue Maybe 
Instance details

Defined in Named.Internal

Methods

injValue :: a -> Maybe a #

PTraversable Maybe 
Instance details

Defined in Data.Singletons.Prelude.Traversable

Associated Types

type Traverse arg arg1 :: f (t b) #

type SequenceA arg :: f (t a) #

type MapM arg arg1 :: m (t b) #

type Sequence arg :: m (t a) #

STraversable Maybe 
Instance details

Defined in Data.Singletons.Prelude.Traversable

Methods

sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: Maybe a). SApplicative f => Sing t1 -> Sing t2 -> Sing (Apply (Apply TraverseSym0 t1) t2) #

sSequenceA :: forall (f :: Type -> Type) a (t1 :: Maybe (f a)). SApplicative f => Sing t1 -> Sing (Apply SequenceASym0 t1) #

sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: Maybe a). SMonad m => Sing t1 -> Sing t2 -> Sing (Apply (Apply MapMSym0 t1) t2) #

sSequence :: forall (m :: Type -> Type) a (t1 :: Maybe (m a)). SMonad m => Sing t1 -> Sing (Apply SequenceSym0 t1) #

PFoldable Maybe 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Associated Types

type Fold arg :: m #

type FoldMap arg arg1 :: m #

type Foldr arg arg1 arg2 :: b #

type Foldr' arg arg1 arg2 :: b #

type Foldl arg arg1 arg2 :: b #

type Foldl' arg arg1 arg2 :: b #

type Foldr1 arg arg1 :: a #

type Foldl1 arg arg1 :: a #

type ToList arg :: [a] #

type Null arg :: Bool #

type Length arg :: Nat #

type Elem arg arg1 :: Bool #

type Maximum arg :: a #

type Minimum arg :: a #

type Sum arg :: a #

type Product arg :: a #

SFoldable Maybe 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sFold :: forall m (t1 :: Maybe m). SMonoid m => Sing t1 -> Sing (Apply FoldSym0 t1) #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Maybe a). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply FoldMapSym0 t1) t2) #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Maybe a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply FoldrSym0 t1) t2) t3) #

sFoldr' :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Maybe a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply Foldr'Sym0 t1) t2) t3) #

sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Maybe a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply FoldlSym0 t1) t2) t3) #

sFoldl' :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Maybe a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply Foldl'Sym0 t1) t2) t3) #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Apply (Apply Foldr1Sym0 t1) t2) #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Apply (Apply Foldl1Sym0 t1) t2) #

sToList :: forall a (t1 :: Maybe a). Sing t1 -> Sing (Apply ToListSym0 t1) #

sNull :: forall a (t1 :: Maybe a). Sing t1 -> Sing (Apply NullSym0 t1) #

sLength :: forall a (t1 :: Maybe a). Sing t1 -> Sing (Apply LengthSym0 t1) #

sElem :: forall a (t1 :: a) (t2 :: Maybe a). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply ElemSym0 t1) t2) #

sMaximum :: forall a (t1 :: Maybe a). SOrd a => Sing t1 -> Sing (Apply MaximumSym0 t1) #

sMinimum :: forall a (t1 :: Maybe a). SOrd a => Sing t1 -> Sing (Apply MinimumSym0 t1) #

sSum :: forall a (t1 :: Maybe a). SNum a => Sing t1 -> Sing (Apply SumSym0 t1) #

sProduct :: forall a (t1 :: Maybe a). SNum a => Sing t1 -> Sing (Apply ProductSym0 t1) #

SMonadFail Maybe 
Instance details

Defined in Data.Singletons.Prelude.Monad.Fail

Methods

sFail :: forall a (t :: [Char]). Sing t -> Sing (Apply FailSym0 t) #

PFunctor Maybe 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

Associated Types

type Fmap arg arg1 :: f b #

type arg <$ arg1 :: f a #

PApplicative Maybe 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

Associated Types

type Pure arg :: f a #

type arg <*> arg1 :: f b #

type LiftA2 arg arg1 arg2 :: f c #

type arg *> arg1 :: f b #

type arg <* arg1 :: f a #

PMonad Maybe 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

Associated Types

type arg >>= arg1 :: m b #

type arg >> arg1 :: m b #

type Return arg :: m a #

SFunctor Maybe 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Apply (Apply FmapSym0 t1) t2) #

(%<$) :: forall a b (t1 :: a) (t2 :: Maybe b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (<$@#@$) t1) t2) #

SApplicative Maybe 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Apply PureSym0 t) #

(%<*>) :: forall a b (t1 :: Maybe (a ~> b)) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (<*>@#@$) t1) t2) #

sLiftA2 :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: Maybe a) (t3 :: Maybe b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply LiftA2Sym0 t1) t2) t3) #

(%*>) :: forall a b (t1 :: Maybe a) (t2 :: Maybe b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (*>@#@$) t1) t2) #

(%<*) :: forall a b (t1 :: Maybe a) (t2 :: Maybe b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (<*@#@$) t1) t2) #

SMonad Maybe 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

Methods

(%>>=) :: forall a b (t1 :: Maybe a) (t2 :: a ~> Maybe b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (>>=@#@$) t1) t2) #

(%>>) :: forall a b (t1 :: Maybe a) (t2 :: Maybe b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (>>@#@$) t1) t2) #

sReturn :: forall a (t :: a). Sing t -> Sing (Apply ReturnSym0 t) #

SAlternative Maybe 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

Methods

sEmpty :: Sing EmptySym0 #

(%<|>) :: forall a (t1 :: Maybe a) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (<|>@#@$) t1) t2) #

SMonadPlus Maybe 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

Methods

sMzero :: Sing MzeroSym0 #

sMplus :: forall a (t1 :: Maybe a) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Apply (Apply MplusSym0 t1) t2) #

KnownNamedFunctor Maybe 
Instance details

Defined in Util.Named

Methods

namedL :: forall (name :: Symbol) a. Label name -> Iso' (NamedF Maybe a name) (ApplyNamedFunctor Maybe a)

LorentzFunctor Maybe Source # 
Instance details

Defined in Lorentz.Instr

Methods

lmap :: forall b a (s :: [Type]). KnownValue b => ((a ': s) :-> (b ': s)) -> (Maybe a ': s) :-> (Maybe b ': s) Source #

(Selector s, GToJSON' enc arity (K1 i (Maybe a) :: Type -> Type), KeyValuePair enc pairs, Monoid pairs) => RecordToPairs enc pairs arity (S1 s (K1 i (Maybe a) :: Type -> Type)) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

recordToPairs :: Options -> ToArgs enc arity a0 -> S1 s (K1 i (Maybe a)) a0 -> pairs

Lift a => Lift (Maybe a :: Type) 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Maybe a -> Q Exp #

liftTyped :: Maybe a -> Q (TExp (Maybe a)) #

() :=> (Functor Maybe) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Functor Maybe #

() :=> (Applicative Maybe) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Applicative Maybe #

() :=> (MonadPlus Maybe) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- MonadPlus Maybe #

() :=> (Alternative Maybe) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Alternative Maybe #

Eq a => Eq (Maybe a)

Since: base-2.1

Instance details

Defined in GHC.Maybe

Methods

(==) :: Maybe a -> Maybe a -> Bool #

(/=) :: Maybe a -> Maybe a -> Bool #

Ord a => Ord (Maybe a)

Since: base-2.1

Instance details

Defined in GHC.Maybe

Methods

compare :: Maybe a -> Maybe a -> Ordering #

(<) :: Maybe a -> Maybe a -> Bool #

(<=) :: Maybe a -> Maybe a -> Bool #

(>) :: Maybe a -> Maybe a -> Bool #

(>=) :: Maybe a -> Maybe a -> Bool #

max :: Maybe a -> Maybe a -> Maybe a #

min :: Maybe a -> Maybe a -> Maybe a #

Read a => Read (Maybe a)

Since: base-2.1

Instance details

Defined in GHC.Read

Show a => Show (Maybe a)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> Maybe a -> ShowS #

show :: Maybe a -> String #

showList :: [Maybe a] -> ShowS #

Generic (Maybe a)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (Maybe a) :: Type -> Type #

Methods

from :: Maybe a -> Rep (Maybe a) x #

to :: Rep (Maybe a) x -> Maybe a #

Semigroup a => Semigroup (Maybe a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(<>) :: Maybe a -> Maybe a -> Maybe a #

sconcat :: NonEmpty (Maybe a) -> Maybe a #

stimes :: Integral b => b -> Maybe a -> Maybe a #

Semigroup a => Monoid (Maybe a)

Lift a semigroup into Maybe forming a Monoid according to http://en.wikipedia.org/wiki/Monoid: "Any semigroup S may be turned into a monoid simply by adjoining an element e not in S and defining e*e = e and e*s = s = s*e for all s ∈ S."

Since 4.11.0: constraint on inner a value generalised from Monoid to Semigroup.

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: Maybe a #

mappend :: Maybe a -> Maybe a -> Maybe a #

mconcat :: [Maybe a] -> Maybe a #

Hashable a => Hashable (Maybe a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Maybe a -> Int #

hash :: Maybe a -> Int #

ToJSON a => ToJSON (Maybe a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

NFData a => NFData (Maybe a) 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Maybe a -> () #

Default (Maybe a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Maybe a #

Buildable a => Buildable (Maybe a) 
Instance details

Defined in Formatting.Buildable

Methods

build :: Maybe a -> Builder #

Ixed (Maybe a) 
Instance details

Defined in Control.Lens.At

Methods

ix :: Index (Maybe a) -> Traversal' (Maybe a) (IxValue (Maybe a)) #

At (Maybe a) 
Instance details

Defined in Control.Lens.At

Methods

at :: Index (Maybe a) -> Lens' (Maybe a) (Maybe (IxValue (Maybe a))) #

Semiring a => Semiring (Maybe a) 
Instance details

Defined in Data.Semiring

Methods

plus :: Maybe a -> Maybe a -> Maybe a #

zero :: Maybe a #

times :: Maybe a -> Maybe a -> Maybe a #

one :: Maybe a #

fromNatural :: Natural -> Maybe a #

PMonoid (Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type Mempty :: a #

type Mappend arg arg1 :: a #

type Mconcat arg :: a #

SSemigroup a => SMonoid (Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Methods

sMempty :: Sing MemptySym0 #

sMappend :: forall (t1 :: Maybe a) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Apply (Apply MappendSym0 t1) t2) #

sMconcat :: forall (t :: [Maybe a]). Sing t -> Sing (Apply MconcatSym0 t) #

PShow (Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Show

Associated Types

type ShowsPrec arg arg1 arg2 :: Symbol #

type Show_ arg :: Symbol #

type ShowList arg arg1 :: Symbol #

SShow a => SShow (Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Show

Methods

sShowsPrec :: forall (t1 :: Nat) (t2 :: Maybe a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply ShowsPrecSym0 t1) t2) t3) #

sShow_ :: forall (t :: Maybe a). Sing t -> Sing (Apply Show_Sym0 t) #

sShowList :: forall (t1 :: [Maybe a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply ShowListSym0 t1) t2) #

PSemigroup (Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg <> arg1 :: a #

type Sconcat arg :: a #

SSemigroup a => SSemigroup (Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

(%<>) :: forall (t1 :: Maybe a) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (<>@#@$) t1) t2) #

sSconcat :: forall (t :: NonEmpty (Maybe a)). Sing t -> Sing (Apply SconcatSym0 t) #

POrd (Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

Associated Types

type Compare arg arg1 :: Ordering #

type arg < arg1 :: Bool #

type arg <= arg1 :: Bool #

type arg > arg1 :: Bool #

type arg >= arg1 :: Bool #

type Max arg arg1 :: a #

type Min arg arg1 :: a #

SOrd a => SOrd (Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

Methods

sCompare :: forall (t1 :: Maybe a) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Apply (Apply CompareSym0 t1) t2) #

(%<) :: forall (t1 :: Maybe a) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (<@#@$) t1) t2) #

(%<=) :: forall (t1 :: Maybe a) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (<=@#@$) t1) t2) #

(%>) :: forall (t1 :: Maybe a) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (>@#@$) t1) t2) #

(%>=) :: forall (t1 :: Maybe a) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (>=@#@$) t1) t2) #

sMax :: forall (t1 :: Maybe a) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Apply (Apply MaxSym0 t1) t2) #

sMin :: forall (t1 :: Maybe a) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Apply (Apply MinSym0 t1) t2) #

SEq a => SEq (Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Eq

Methods

(%==) :: forall (a0 :: Maybe a) (b :: Maybe a). Sing a0 -> Sing b -> Sing (a0 == b) #

(%/=) :: forall (a0 :: Maybe a) (b :: Maybe a). Sing a0 -> Sing b -> Sing (a0 /= b) #

PEq (Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Eq

Associated Types

type x == y :: Bool #

type x /= y :: Bool #

(TypeError (DisallowInstance "Maybe") :: Constraint) => Container (Maybe a) 
Instance details

Defined in Universum.Container.Class

Associated Types

type Element (Maybe a) #

Methods

toList :: Maybe a -> [Element (Maybe a)] #

null :: Maybe a -> Bool #

foldr :: (Element (Maybe a) -> b -> b) -> b -> Maybe a -> b #

foldl :: (b -> Element (Maybe a) -> b) -> b -> Maybe a -> b #

foldl' :: (b -> Element (Maybe a) -> b) -> b -> Maybe a -> b #

length :: Maybe a -> Int #

elem :: Element (Maybe a) -> Maybe a -> Bool #

maximum :: Maybe a -> Element (Maybe a) #

minimum :: Maybe a -> Element (Maybe a) #

foldMap :: Monoid m => (Element (Maybe a) -> m) -> Maybe a -> m #

fold :: Maybe a -> Element (Maybe a) #

foldr' :: (Element (Maybe a) -> b -> b) -> b -> Maybe a -> b #

foldr1 :: (Element (Maybe a) -> Element (Maybe a) -> Element (Maybe a)) -> Maybe a -> Element (Maybe a) #

foldl1 :: (Element (Maybe a) -> Element (Maybe a) -> Element (Maybe a)) -> Maybe a -> Element (Maybe a) #

notElem :: Element (Maybe a) -> Maybe a -> Bool #

all :: (Element (Maybe a) -> Bool) -> Maybe a -> Bool #

any :: (Element (Maybe a) -> Bool) -> Maybe a -> Bool #

and :: Maybe a -> Bool #

or :: Maybe a -> Bool #

find :: (Element (Maybe a) -> Bool) -> Maybe a -> Maybe (Element (Maybe a)) #

safeHead :: Maybe a -> Maybe (Element (Maybe a)) #

Pretty a => Pretty (Maybe a) 
Instance details

Defined in Text.PrettyPrint.Leijen.Text

Methods

pretty :: Maybe a -> Doc #

prettyList :: [Maybe a] -> Doc #

SingKind a => SingKind (Maybe a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type DemoteRep (Maybe a)

Methods

fromSing :: forall (a0 :: Maybe a). Sing a0 -> DemoteRep (Maybe a)

PolyTypeHasDocC '[a] => TypeHasDoc (Maybe a) 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions (Maybe a) :: FieldDescriptions #

Methods

typeDocName :: Proxy (Maybe a) -> Text #

typeDocMdDescription :: Markdown #

typeDocMdReference :: Proxy (Maybe a) -> WithinParens -> Markdown #

typeDocDependencies :: Proxy (Maybe a) -> [SomeDocDefinitionItem] #

typeDocHaskellRep :: TypeDocHaskellRep (Maybe a) #

typeDocMichelsonRep :: TypeDocMichelsonRep (Maybe a) #

IsoValue a => IsoValue (Maybe a) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (Maybe a) :: T #

Methods

toVal :: Maybe a -> Value (ToT (Maybe a)) #

fromVal :: Value (ToT (Maybe a)) -> Maybe a #

HasAnnotation a => HasAnnotation (Maybe a) Source # 
Instance details

Defined in Lorentz.Annotation

Generic1 Maybe

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Maybe :: k -> Type #

Methods

from1 :: forall (a :: k). Maybe a -> Rep1 Maybe a #

to1 :: forall (a :: k). Rep1 Maybe a -> Maybe a #

PMonadFail Maybe 
Instance details

Defined in Data.Singletons.Prelude.Monad.Fail

Associated Types

type Fail arg :: m a #

PAlternative Maybe 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

Associated Types

type Empty :: f a #

type arg <|> arg1 :: f a #

PMonadPlus Maybe 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

Associated Types

type Mzero :: m a #

type Mplus arg arg1 :: m a #

IsoHKD Maybe (a :: Type) 
Instance details

Defined in Data.Vinyl.XRec

Associated Types

type HKD Maybe a #

Methods

unHKD :: HKD Maybe a -> Maybe a #

toHKD :: Maybe a -> HKD Maybe a #

SDecide a => TestCoercion (SMaybe :: Maybe a -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Instances

Methods

testCoercion :: forall (a0 :: k) (b :: k). SMaybe a0 -> SMaybe b -> Maybe (Coercion a0 b) #

SDecide a => TestEquality (SMaybe :: Maybe a -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Instances

Methods

testEquality :: forall (a0 :: k) (b :: k). SMaybe a0 -> SMaybe b -> Maybe (a0 :~: b) #

(Eq a) :=> (Eq (Maybe a)) 
Instance details

Defined in Data.Constraint

Methods

ins :: Eq a :- Eq (Maybe a) #

(Ord a) :=> (Ord (Maybe a)) 
Instance details

Defined in Data.Constraint

Methods

ins :: Ord a :- Ord (Maybe a) #

(Read a) :=> (Read (Maybe a)) 
Instance details

Defined in Data.Constraint

Methods

ins :: Read a :- Read (Maybe a) #

(Show a) :=> (Show (Maybe a)) 
Instance details

Defined in Data.Constraint

Methods

ins :: Show a :- Show (Maybe a) #

(Semigroup a) :=> (Semigroup (Maybe a)) 
Instance details

Defined in Data.Constraint

Methods

ins :: Semigroup a :- Semigroup (Maybe a) #

(Monoid a) :=> (Monoid (Maybe a)) 
Instance details

Defined in Data.Constraint

Methods

ins :: Monoid a :- Monoid (Maybe a) #

SingI ('Nothing :: Maybe a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing 'Nothing

Each (Maybe a) (Maybe b) a b 
Instance details

Defined in Lens.Micro.Internal

Methods

each :: Traversal (Maybe a) (Maybe b) a b #

CanCastTo a b => CanCastTo (Maybe a :: Type) (Maybe b :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (Maybe a) -> Proxy (Maybe b) -> () Source #

SingI a2 => SingI ('Just a2 :: Maybe a1)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing ('Just a2)

SuppressUnusedWarnings (Fail_6989586621680155600Sym0 :: TyFun [Char] (Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Fail

SuppressUnusedWarnings (CatMaybesSym0 :: TyFun [Maybe a] [a] -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (ListToMaybeSym0 :: TyFun [a] (Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (StripPrefixSym0 :: TyFun [a] ([a] ~> Maybe [a]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (TFHelper_6989586621680072421Sym0 :: TyFun (Maybe a) (Maybe a ~> Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (MaybeToListSym0 :: TyFun (Maybe a) [a] -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (IsNothingSym0 :: TyFun (Maybe a) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (IsJustSym0 :: TyFun (Maybe a) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (FromJustSym0 :: TyFun (Maybe a) a -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (MinInternalSym0 :: TyFun (Maybe a) (MinInternal a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (MaxInternalSym0 :: TyFun (Maybe a) (MaxInternal a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Compare_6989586621679847835Sym0 :: TyFun (Maybe a) (Maybe a ~> Ordering) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (TFHelper_6989586621680240170Sym0 :: TyFun (Maybe a) (Maybe a ~> Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

SuppressUnusedWarnings (OptionSym0 :: TyFun (Maybe a) (Option a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

SuppressUnusedWarnings (LastSym0 :: TyFun (Maybe a) (Last a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

SuppressUnusedWarnings (FirstSym0 :: TyFun (Maybe a) (First a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

SuppressUnusedWarnings (ShowsPrec_6989586621680653283Sym0 :: TyFun Nat (Maybe a ~> (Symbol ~> Symbol)) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings (Pure_6989586621680072163Sym0 :: TyFun a (Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (Let6989586621680072430LSym0 :: TyFun k1 (Maybe k1) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (FromMaybeSym0 :: TyFun a (Maybe a ~> a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Nat) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (JustSym0 :: TyFun a (Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Instances

SuppressUnusedWarnings (GetOptionSym0 :: TyFun (Option a) (Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

SuppressUnusedWarnings (GetFirstSym0 :: TyFun (First a) (Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

SuppressUnusedWarnings (GetLastSym0 :: TyFun (Last a) (Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

SuppressUnusedWarnings (FindSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Nat) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (GetMaxInternalSym0 :: TyFun (MaxInternal a) (Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (GetMinInternalSym0 :: TyFun (MinInternal a) (Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SingI (CatMaybesSym0 :: TyFun [Maybe a] [a] -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SingI (ListToMaybeSym0 :: TyFun [a] (Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SingI (MaybeToListSym0 :: TyFun (Maybe a) [a] -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SingI (IsNothingSym0 :: TyFun (Maybe a) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SingI (IsJustSym0 :: TyFun (Maybe a) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

Methods

sing :: Sing IsJustSym0 #

SingI (FromJustSym0 :: TyFun (Maybe a) a -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SingI (MinInternalSym0 :: TyFun (Maybe a) (MinInternal a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing MinInternalSym0 #

SingI (MaxInternalSym0 :: TyFun (Maybe a) (MaxInternal a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing MaxInternalSym0 #

SingI (OptionSym0 :: TyFun (Maybe a) (Option a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

sing :: Sing OptionSym0 #

SingI (LastSym0 :: TyFun (Maybe a) (Last a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Methods

sing :: Sing LastSym0 #

SingI (FirstSym0 :: TyFun (Maybe a) (First a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Methods

sing :: Sing FirstSym0 #

SingI (FromMaybeSym0 :: TyFun a (Maybe a ~> a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SEq a => SingI (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Nat) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SingI (JustSym0 :: TyFun a (Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Instances

Methods

sing :: Sing JustSym0 #

SingI (GetOptionSym0 :: TyFun (Option a) (Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

SingI (GetFirstSym0 :: TyFun (First a) (Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

SingI (GetLastSym0 :: TyFun (Last a) (Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

SingI (FindSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing FindSym0 #

SingI (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Nat) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SingI (GetMaxInternalSym0 :: TyFun (MaxInternal a) (Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing GetMaxInternalSym0 #

SingI (GetMinInternalSym0 :: TyFun (MinInternal a) (Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing GetMinInternalSym0 #

SuppressUnusedWarnings (StripPrefixSym1 a6989586621680498340 :: TyFun [a] (Maybe [a]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (FindSym1 a6989586621680379018 :: TyFun [a] (Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (FindIndexSym1 a6989586621680378991 :: TyFun [a] (Maybe Nat) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (ElemIndexSym1 a6989586621680379009 :: TyFun [a] (Maybe Nat) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (ShowsPrec_6989586621680653283Sym1 a6989586621680653293 :: TyFun (Maybe a) (Symbol ~> Symbol) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings (TFHelper_6989586621680072421Sym1 a6989586621680072426 :: TyFun (Maybe a) (Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (TFHelper_6989586621680072345Sym0 :: TyFun (Maybe a) (Maybe b ~> Maybe b) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (TFHelper_6989586621680072334Sym0 :: TyFun (Maybe a) ((a ~> Maybe b) ~> Maybe b) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (TFHelper_6989586621680072200Sym0 :: TyFun (Maybe a) (Maybe b ~> Maybe b) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (FromMaybeSym1 a6989586621679958789 :: TyFun (Maybe a) a -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (Compare_6989586621679847835Sym1 a6989586621679847840 :: TyFun (Maybe a) Ordering -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (TFHelper_6989586621680240170Sym1 a6989586621680240175 :: TyFun (Maybe a) (Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

SuppressUnusedWarnings (TFHelper_6989586621680072173Sym0 :: TyFun (Maybe (a ~> b)) (Maybe a ~> Maybe b) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (OptionalSym0 :: TyFun (f a) (f (Maybe a)) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Applicative

SuppressUnusedWarnings (TFHelper_6989586621680072052Sym0 :: TyFun a (Maybe b ~> Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (Maybe_Sym0 :: TyFun b ((a ~> b) ~> (Maybe a ~> b)) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680822397MkJustSym0 :: TyFun k (TyFun a6989586621680821555 (Maybe a6989586621680821555) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680822382MkJustSym0 :: TyFun k (TyFun a6989586621680821554 (Maybe a6989586621680821554) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680813466NSym0 :: TyFun k (TyFun k1 (Maybe k1) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680813466MSym0 :: TyFun k1 (TyFun k (Maybe k1) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680813442NSym0 :: TyFun k (TyFun k1 (Maybe k1) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680813442MSym0 :: TyFun k1 (TyFun k (Maybe k1) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Fmap_6989586621680072040Sym0 :: TyFun (a ~> b) (Maybe a ~> Maybe b) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (MapMaybeSym0 :: TyFun (a ~> Maybe b) ([a] ~> [b]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Foldr_6989586621680822439Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (Maybe a ~> b)) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Foldl_6989586621680822455Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (Maybe a ~> b)) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (FoldMap_6989586621680822423Sym0 :: TyFun (a ~> m) (Maybe a ~> m) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SingI d => SingI (FindSym1 d :: TyFun [a] (Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (FindSym1 d) #

SingI d => SingI (FindIndexSym1 d :: TyFun [a] (Maybe Nat) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (FindIndexSym1 d) #

(SEq a, SingI d) => SingI (ElemIndexSym1 d :: TyFun [a] (Maybe Nat) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (ElemIndexSym1 d) #

SingI d => SingI (FromMaybeSym1 d :: TyFun (Maybe a) a -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

Methods

sing :: Sing (FromMaybeSym1 d) #

SAlternative f => SingI (OptionalSym0 :: TyFun (f a) (f (Maybe a)) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Applicative

SingI (Maybe_Sym0 :: TyFun b ((a ~> b) ~> (Maybe a ~> b)) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

Methods

sing :: Sing Maybe_Sym0 #

SEq a => SingI (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing LookupSym0 #

SingI (MapMaybeSym0 :: TyFun (a ~> Maybe b) ([a] ~> [b]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SingI (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SFoldable t => SingI (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing FindSym0 #

SuppressUnusedWarnings (LookupSym1 a6989586621680378716 :: TyFun [(a, b)] (Maybe b) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (TFHelper_6989586621680072345Sym1 a6989586621680072354 :: TyFun (Maybe b) (Maybe b) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (TFHelper_6989586621680072200Sym1 a6989586621680072205 :: TyFun (Maybe b) (Maybe b) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (TFHelper_6989586621680072173Sym1 a6989586621680072178 :: TyFun (Maybe a) (Maybe b) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (TFHelper_6989586621680072052Sym1 a6989586621680072057 :: TyFun (Maybe b) (Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (Fmap_6989586621680072040Sym1 a6989586621680072045 :: TyFun (Maybe a) (Maybe b) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (FoldMap_6989586621680822423Sym1 a6989586621680822432 :: TyFun (Maybe a) m -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680822397MkJustSym1 a_69895866216808223916989586621680822396 :: TyFun a6989586621680821555 (Maybe a6989586621680821555) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680822382MkJustSym1 a_69895866216808223766989586621680822381 :: TyFun a6989586621680821554 (Maybe a6989586621680821554) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680813466NSym1 x6989586621680813464 :: TyFun k1 (Maybe k1) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680813466MSym1 x6989586621680813464 :: TyFun k (Maybe k1) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680813442NSym1 x6989586621680813440 :: TyFun k1 (Maybe k1) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680813442MSym1 x6989586621680813440 :: TyFun k (Maybe k1) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Foldr_6989586621680822439Sym1 a6989586621680822445 :: TyFun b (Maybe a ~> b) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Foldl_6989586621680822455Sym1 a6989586621680822461 :: TyFun b (Maybe a ~> b) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (FindSym1 a6989586621680821889 :: TyFun (t a) (Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Lambda_6989586621680700471Sym0 :: TyFun k (TyFun (k1 ~> Last a) (TyFun k1 (Maybe a) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

SuppressUnusedWarnings (Lambda_6989586621680700392Sym0 :: TyFun k (TyFun (k1 ~> First a) (TyFun k1 (Maybe a) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

SuppressUnusedWarnings (Traverse_6989586621681087642Sym0 :: TyFun (a ~> f b) (Maybe a ~> f (Maybe b)) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Traversable

SuppressUnusedWarnings (TFHelper_6989586621680072334Sym1 a6989586621680072339 :: TyFun (a ~> Maybe b) (Maybe b) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (LiftA2_6989586621680072186Sym0 :: TyFun (a ~> (b ~> c)) (Maybe a ~> (Maybe b ~> Maybe c)) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (Maybe_Sym1 a6989586621679957223 :: TyFun (a ~> b) (Maybe a ~> b) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (Let6989586621679958764RsSym0 :: TyFun (a ~> Maybe k1) (TyFun k (TyFun [a] [k1] -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (Let6989586621680822304MfSym0 :: TyFun (k2 ~> (k3 ~> k3)) (TyFun k (TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680822283MfSym0 :: TyFun (k2 ~> (k3 ~> k2)) (TyFun k (TyFun k2 (TyFun (Maybe k3) (Maybe k2) -> Type) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

(SEq a, SingI d) => SingI (LookupSym1 d :: TyFun [(a, b)] (Maybe b) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (LookupSym1 d) #

(SFoldable t, SingI d) => SingI (FindSym1 d :: TyFun (t a) (Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (FindSym1 d) #

SingI d => SingI (Maybe_Sym1 d :: TyFun (a ~> b) (Maybe a ~> b) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

Methods

sing :: Sing (Maybe_Sym1 d) #

SuppressUnusedWarnings (Traverse_6989586621681087642Sym1 a6989586621681087647 :: TyFun (Maybe a) (f (Maybe b)) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Traversable

SuppressUnusedWarnings (LiftA2_6989586621680072186Sym1 a6989586621680072192 :: TyFun (Maybe a) (Maybe b ~> Maybe c) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (Maybe_Sym2 a6989586621679957223 a6989586621679957224 :: TyFun (Maybe a) b -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (Foldr_6989586621680822439Sym2 a6989586621680822445 a6989586621680822446 :: TyFun (Maybe a) b -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Foldl_6989586621680822455Sym2 a6989586621680822461 a6989586621680822462 :: TyFun (Maybe a) b -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680822304MfSym1 f6989586621680822302 :: TyFun k (TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680822283MfSym1 f6989586621680822281 :: TyFun k (TyFun k2 (TyFun (Maybe k3) (Maybe k2) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Lambda_6989586621680700471Sym1 a6989586621680700469 :: TyFun (k1 ~> Last a) (TyFun k1 (Maybe a) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

SuppressUnusedWarnings (Lambda_6989586621680700392Sym1 a6989586621680700390 :: TyFun (k1 ~> First a) (TyFun k1 (Maybe a) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

(SingI d1, SingI d2) => SingI (Maybe_Sym2 d1 d2 :: TyFun (Maybe a) b -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

Methods

sing :: Sing (Maybe_Sym2 d1 d2) #

SuppressUnusedWarnings (LiftA2_6989586621680072186Sym2 a6989586621680072192 a6989586621680072193 :: TyFun (Maybe b) (Maybe c) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (Let6989586621680822304MfSym2 f6989586621680822302 xs6989586621680822303 :: TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680822283MfSym2 f6989586621680822281 xs6989586621680822282 :: TyFun k2 (TyFun (Maybe k3) (Maybe k2) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Lambda_6989586621680700471Sym2 a6989586621680700469 k6989586621680700470 :: TyFun k1 (Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

SuppressUnusedWarnings (Lambda_6989586621680700392Sym2 a6989586621680700390 k6989586621680700391 :: TyFun k1 (Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

SuppressUnusedWarnings (Let6989586621680822283MfSym3 f6989586621680822281 xs6989586621680822282 a6989586621680822284 :: TyFun (Maybe k3) (Maybe k2) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680822304MfSym3 f6989586621680822302 xs6989586621680822303 a6989586621680822305 :: TyFun k3 (Maybe k3) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

IsoValue a => IsoValue (NamedF Maybe a name) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (NamedF Maybe a name) :: T #

Methods

toVal :: NamedF Maybe a name -> Value (ToT (NamedF Maybe a name)) #

fromVal :: Value (ToT (NamedF Maybe a name)) -> NamedF Maybe a name #

(HasAnnotation (Maybe a), KnownSymbol name) => HasAnnotation (NamedF Maybe a name) Source # 
Instance details

Defined in Lorentz.Annotation

Wrappable (NamedF Maybe a name) Source # 
Instance details

Defined in Lorentz.Wrappable

Associated Types

type Unwrappable (NamedF Maybe a name) Source #

type Failure Maybe 
Instance details

Defined in Basement.Monad

type Failure Maybe = ()
type Product (arg :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Product (arg :: Maybe a) = Apply (Product_6989586621680822413Sym0 :: TyFun (Maybe a) a -> Type) arg
type Sum (arg :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Sum (arg :: Maybe a) = Apply (Sum_6989586621680822404Sym0 :: TyFun (Maybe a) a -> Type) arg
type Minimum (arg :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Minimum (arg :: Maybe a) = Apply (Minimum_6989586621680822389Sym0 :: TyFun (Maybe a) a -> Type) arg
type Maximum (arg :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Maximum (arg :: Maybe a) = Apply (Maximum_6989586621680822374Sym0 :: TyFun (Maybe a) a -> Type) arg
type Length (arg :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Length (arg :: Maybe a) = Apply (Length_6989586621680822341Sym0 :: TyFun (Maybe a) Nat -> Type) arg
type Null (arg :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Null (arg :: Maybe a) = Apply (Null_6989586621680822324Sym0 :: TyFun (Maybe a) Bool -> Type) arg
type ToList (arg :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type ToList (arg :: Maybe a) = Apply (ToList_6989586621680822315Sym0 :: TyFun (Maybe a) [a] -> Type) arg
type Fold (arg :: Maybe m) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Fold (arg :: Maybe m) = Apply (Fold_6989586621680822175Sym0 :: TyFun (Maybe m) m -> Type) arg
type Pure (a :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Pure (a :: k1) = Apply (Pure_6989586621680072163Sym0 :: TyFun k1 (Maybe k1) -> Type) a
type Return (arg :: a) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Return (arg :: a) = Apply (Return_6989586621680011394Sym0 :: TyFun a (Maybe a) -> Type) arg
type Sequence (arg :: Maybe (m a)) 
Instance details

Defined in Data.Singletons.Prelude.Traversable

type Sequence (arg :: Maybe (m a)) = Apply (Sequence_6989586621681081437Sym0 :: TyFun (Maybe (m a)) (m (Maybe a)) -> Type) arg
type SequenceA (arg :: Maybe (f a)) 
Instance details

Defined in Data.Singletons.Prelude.Traversable

type SequenceA (arg :: Maybe (f a)) = Apply (SequenceA_6989586621681081413Sym0 :: TyFun (Maybe (f a)) (f (Maybe a)) -> Type) arg
type Elem (arg1 :: a) (arg2 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Elem (arg1 :: a) (arg2 :: Maybe a) = Apply (Apply (Elem_6989586621680822360Sym0 :: TyFun a (Maybe a ~> Bool) -> Type) arg1) arg2
type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Maybe a) = Apply (Apply (Foldl1_6989586621680822295Sym0 :: TyFun (a ~> (a ~> a)) (Maybe a ~> a) -> Type) arg1) arg2
type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Maybe a) = Apply (Apply (Foldr1_6989586621680822274Sym0 :: TyFun (a ~> (a ~> a)) (Maybe a ~> a) -> Type) arg1) arg2
type FoldMap (a2 :: a1 ~> k2) (a3 :: Maybe a1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type FoldMap (a2 :: a1 ~> k2) (a3 :: Maybe a1) = Apply (Apply (FoldMap_6989586621680822423Sym0 :: TyFun (a1 ~> k2) (Maybe a1 ~> k2) -> Type) a2) a3
type (a1 :: k1) <$ (a2 :: Maybe b) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type (a1 :: k1) <$ (a2 :: Maybe b) = Apply (Apply (TFHelper_6989586621680072052Sym0 :: TyFun k1 (Maybe b ~> Maybe k1) -> Type) a1) a2
type Fmap (a2 :: a1 ~> b) (a3 :: Maybe a1) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Fmap (a2 :: a1 ~> b) (a3 :: Maybe a1) = Apply (Apply (Fmap_6989586621680072040Sym0 :: TyFun (a1 ~> b) (Maybe a1 ~> Maybe b) -> Type) a2) a3
type (arg1 :: Maybe a) <* (arg2 :: Maybe b) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type (arg1 :: Maybe a) <* (arg2 :: Maybe b) = Apply (Apply (TFHelper_6989586621680011349Sym0 :: TyFun (Maybe a) (Maybe b ~> Maybe a) -> Type) arg1) arg2
type (a2 :: Maybe a1) *> (a3 :: Maybe b) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type (a2 :: Maybe a1) *> (a3 :: Maybe b) = Apply (Apply (TFHelper_6989586621680072200Sym0 :: TyFun (Maybe a1) (Maybe b ~> Maybe b) -> Type) a2) a3
type (a2 :: Maybe (a1 ~> b)) <*> (a3 :: Maybe a1) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type (a2 :: Maybe (a1 ~> b)) <*> (a3 :: Maybe a1) = Apply (Apply (TFHelper_6989586621680072173Sym0 :: TyFun (Maybe (a1 ~> b)) (Maybe a1 ~> Maybe b) -> Type) a2) a3
type (a2 :: Maybe a1) >> (a3 :: Maybe b) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type (a2 :: Maybe a1) >> (a3 :: Maybe b) = Apply (Apply (TFHelper_6989586621680072345Sym0 :: TyFun (Maybe a1) (Maybe b ~> Maybe b) -> Type) a2) a3
type (a2 :: Maybe a1) >>= (a3 :: a1 ~> Maybe b) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type (a2 :: Maybe a1) >>= (a3 :: a1 ~> Maybe b) = Apply (Apply (TFHelper_6989586621680072334Sym0 :: TyFun (Maybe a1) ((a1 ~> Maybe b) ~> Maybe b) -> Type) a2) a3
type MapM (arg1 :: a ~> m b) (arg2 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Traversable

type MapM (arg1 :: a ~> m b) (arg2 :: Maybe a) = Apply (Apply (MapM_6989586621681081423Sym0 :: TyFun (a ~> m b) (Maybe a ~> m (Maybe b)) -> Type) arg1) arg2
type Traverse (a2 :: a1 ~> f b) (a3 :: Maybe a1) 
Instance details

Defined in Data.Singletons.Prelude.Traversable

type Traverse (a2 :: a1 ~> f b) (a3 :: Maybe a1) = Apply (Apply (Traverse_6989586621681087642Sym0 :: TyFun (a1 ~> f b) (Maybe a1 ~> f (Maybe b)) -> Type) a2) a3
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Maybe a) = Apply (Apply (Apply (Foldl'_6989586621680822252Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (Maybe a ~> b)) -> Type) arg1) arg2) arg3
type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Maybe a1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Maybe a1) = Apply (Apply (Apply (Foldl_6989586621680822455Sym0 :: TyFun (k2 ~> (a1 ~> k2)) (k2 ~> (Maybe a1 ~> k2)) -> Type) a2) a3) a4
type Foldr' (arg1 :: a ~> (b ~> b)) (arg2 :: b) (arg3 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldr' (arg1 :: a ~> (b ~> b)) (arg2 :: b) (arg3 :: Maybe a) = Apply (Apply (Apply (Foldr'_6989586621680822214Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (Maybe a ~> b)) -> Type) arg1) arg2) arg3
type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Maybe a1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Maybe a1) = Apply (Apply (Apply (Foldr_6989586621680822439Sym0 :: TyFun (a1 ~> (k2 ~> k2)) (k2 ~> (Maybe a1 ~> k2)) -> Type) a2) a3) a4
type LiftA2 (a2 :: a1 ~> (b ~> c)) (a3 :: Maybe a1) (a4 :: Maybe b) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type LiftA2 (a2 :: a1 ~> (b ~> c)) (a3 :: Maybe a1) (a4 :: Maybe b) = Apply (Apply (Apply (LiftA2_6989586621680072186Sym0 :: TyFun (a1 ~> (b ~> c)) (Maybe a1 ~> (Maybe b ~> Maybe c)) -> Type) a2) a3) a4
type Apply (Pure_6989586621680072163Sym0 :: TyFun a (Maybe a) -> Type) (a6989586621680072169 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (Pure_6989586621680072163Sym0 :: TyFun a (Maybe a) -> Type) (a6989586621680072169 :: a) = Pure_6989586621680072163Sym1 a6989586621680072169
type Apply (Let6989586621680072430LSym0 :: TyFun k1 (Maybe k1) -> Type) (wild_69895866216800715286989586621680072429 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (Let6989586621680072430LSym0 :: TyFun k1 (Maybe k1) -> Type) (wild_69895866216800715286989586621680072429 :: k1) = Let6989586621680072430LSym1 wild_69895866216800715286989586621680072429
type Apply (JustSym0 :: TyFun a (Maybe a) -> Type) (a6989586621679749471 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Apply (JustSym0 :: TyFun a (Maybe a) -> Type) (a6989586621679749471 :: a) = JustSym1 a6989586621679749471
type Apply (Let6989586621680813442NSym1 x6989586621680813440 :: TyFun k1 (Maybe k1) -> Type) (y6989586621680813441 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680813442NSym1 x6989586621680813440 :: TyFun k1 (Maybe k1) -> Type) (y6989586621680813441 :: k1) = Let6989586621680813442NSym2 x6989586621680813440 y6989586621680813441
type Apply (Let6989586621680813442MSym1 x6989586621680813440 :: TyFun k (Maybe k1) -> Type) (y6989586621680813441 :: k) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680813442MSym1 x6989586621680813440 :: TyFun k (Maybe k1) -> Type) (y6989586621680813441 :: k) = Let6989586621680813442MSym2 x6989586621680813440 y6989586621680813441
type Apply (Let6989586621680813466NSym1 x6989586621680813464 :: TyFun k1 (Maybe k1) -> Type) (y6989586621680813465 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680813466NSym1 x6989586621680813464 :: TyFun k1 (Maybe k1) -> Type) (y6989586621680813465 :: k1) = Let6989586621680813466NSym2 x6989586621680813464 y6989586621680813465
type Apply (Let6989586621680813466MSym1 x6989586621680813464 :: TyFun k (Maybe k1) -> Type) (y6989586621680813465 :: k) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680813466MSym1 x6989586621680813464 :: TyFun k (Maybe k1) -> Type) (y6989586621680813465 :: k) = Let6989586621680813466MSym2 x6989586621680813464 y6989586621680813465
type Apply (Let6989586621680822382MkJustSym1 a_69895866216808223766989586621680822381 :: TyFun a6989586621680821554 (Maybe a6989586621680821554) -> Type) (a6989586621680822385 :: a6989586621680821554) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680822382MkJustSym1 a_69895866216808223766989586621680822381 :: TyFun a6989586621680821554 (Maybe a6989586621680821554) -> Type) (a6989586621680822385 :: a6989586621680821554) = Let6989586621680822382MkJustSym2 a_69895866216808223766989586621680822381 a6989586621680822385
type Apply (Let6989586621680822397MkJustSym1 a_69895866216808223916989586621680822396 :: TyFun a6989586621680821555 (Maybe a6989586621680821555) -> Type) (a6989586621680822400 :: a6989586621680821555) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680822397MkJustSym1 a_69895866216808223916989586621680822396 :: TyFun a6989586621680821555 (Maybe a6989586621680821555) -> Type) (a6989586621680822400 :: a6989586621680821555) = Let6989586621680822397MkJustSym2 a_69895866216808223916989586621680822396 a6989586621680822400
type Apply (Lambda_6989586621680700392Sym2 a6989586621680700390 k6989586621680700391 :: TyFun k1 (Maybe a) -> Type) (x6989586621680700394 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (Lambda_6989586621680700392Sym2 a6989586621680700390 k6989586621680700391 :: TyFun k1 (Maybe a) -> Type) (x6989586621680700394 :: k1) = Lambda_6989586621680700392Sym3 a6989586621680700390 k6989586621680700391 x6989586621680700394
type Apply (Lambda_6989586621680700471Sym2 a6989586621680700469 k6989586621680700470 :: TyFun k1 (Maybe a) -> Type) (x6989586621680700473 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (Lambda_6989586621680700471Sym2 a6989586621680700469 k6989586621680700470 :: TyFun k1 (Maybe a) -> Type) (x6989586621680700473 :: k1) = Lambda_6989586621680700471Sym3 a6989586621680700469 k6989586621680700470 x6989586621680700473
type Apply (Let6989586621680822304MfSym3 f6989586621680822302 xs6989586621680822303 a6989586621680822305 :: TyFun k3 (Maybe k3) -> Type) (a6989586621680822306 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680822304MfSym3 f6989586621680822302 xs6989586621680822303 a6989586621680822305 :: TyFun k3 (Maybe k3) -> Type) (a6989586621680822306 :: k3) = Let6989586621680822304MfSym4 f6989586621680822302 xs6989586621680822303 a6989586621680822305 a6989586621680822306
type Apply (ShowsPrec_6989586621680653283Sym0 :: TyFun Nat (Maybe a ~> (Symbol ~> Symbol)) -> Type) (a6989586621680653293 :: Nat) 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowsPrec_6989586621680653283Sym0 :: TyFun Nat (Maybe a ~> (Symbol ~> Symbol)) -> Type) (a6989586621680653293 :: Nat) = ShowsPrec_6989586621680653283Sym1 a6989586621680653293 :: TyFun (Maybe a) (Symbol ~> Symbol) -> Type
type Apply (FromMaybeSym0 :: TyFun a (Maybe a ~> a) -> Type) (a6989586621679958789 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (FromMaybeSym0 :: TyFun a (Maybe a ~> a) -> Type) (a6989586621679958789 :: a) = FromMaybeSym1 a6989586621679958789
type Apply (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Nat) -> Type) (a6989586621680379009 :: a) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Nat) -> Type) (a6989586621680379009 :: a) = ElemIndexSym1 a6989586621680379009
type Apply (TFHelper_6989586621680072052Sym0 :: TyFun a (Maybe b ~> Maybe a) -> Type) (a6989586621680072057 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621680072052Sym0 :: TyFun a (Maybe b ~> Maybe a) -> Type) (a6989586621680072057 :: a) = TFHelper_6989586621680072052Sym1 a6989586621680072057 :: TyFun (Maybe b) (Maybe a) -> Type
type Apply (Maybe_Sym0 :: TyFun b ((a ~> b) ~> (Maybe a ~> b)) -> Type) (a6989586621679957223 :: b) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (Maybe_Sym0 :: TyFun b ((a ~> b) ~> (Maybe a ~> b)) -> Type) (a6989586621679957223 :: b) = Maybe_Sym1 a6989586621679957223 :: TyFun (a ~> b) (Maybe a ~> b) -> Type
type Apply (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) (a6989586621680378716 :: a) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) (a6989586621680378716 :: a) = LookupSym1 a6989586621680378716 :: TyFun [(a, b)] (Maybe b) -> Type
type Apply (Let6989586621680813442NSym0 :: TyFun k (TyFun k1 (Maybe k1) -> Type) -> Type) (x6989586621680813440 :: k) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680813442NSym0 :: TyFun k (TyFun k1 (Maybe k1) -> Type) -> Type) (x6989586621680813440 :: k) = Let6989586621680813442NSym1 x6989586621680813440 :: TyFun k1 (Maybe k1) -> Type
type Apply (Let6989586621680813442MSym0 :: TyFun k1 (TyFun k (Maybe k1) -> Type) -> Type) (x6989586621680813440 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680813442MSym0 :: TyFun k1 (TyFun k (Maybe k1) -> Type) -> Type) (x6989586621680813440 :: k1) = Let6989586621680813442MSym1 x6989586621680813440 :: TyFun k (Maybe k1) -> Type
type Apply (Let6989586621680813466NSym0 :: TyFun k (TyFun k1 (Maybe k1) -> Type) -> Type) (x6989586621680813464 :: k) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680813466NSym0 :: TyFun k (TyFun k1 (Maybe k1) -> Type) -> Type) (x6989586621680813464 :: k) = Let6989586621680813466NSym1 x6989586621680813464 :: TyFun k1 (Maybe k1) -> Type
type Apply (Let6989586621680813466MSym0 :: TyFun k1 (TyFun k (Maybe k1) -> Type) -> Type) (x6989586621680813464 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680813466MSym0 :: TyFun k1 (TyFun k (Maybe k1) -> Type) -> Type) (x6989586621680813464 :: k1) = Let6989586621680813466MSym1 x6989586621680813464 :: TyFun k (Maybe k1) -> Type
type Apply (Let6989586621680822382MkJustSym0 :: TyFun k (TyFun a6989586621680821554 (Maybe a6989586621680821554) -> Type) -> Type) (a_69895866216808223766989586621680822381 :: k) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680822382MkJustSym0 :: TyFun k (TyFun a6989586621680821554 (Maybe a6989586621680821554) -> Type) -> Type) (a_69895866216808223766989586621680822381 :: k) = Let6989586621680822382MkJustSym1 a_69895866216808223766989586621680822381 :: TyFun a6989586621680821554 (Maybe a6989586621680821554) -> Type
type Apply (Let6989586621680822397MkJustSym0 :: TyFun k (TyFun a6989586621680821555 (Maybe a6989586621680821555) -> Type) -> Type) (a_69895866216808223916989586621680822396 :: k) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680822397MkJustSym0 :: TyFun k (TyFun a6989586621680821555 (Maybe a6989586621680821555) -> Type) -> Type) (a_69895866216808223916989586621680822396 :: k) = Let6989586621680822397MkJustSym1 a_69895866216808223916989586621680822396 :: TyFun a6989586621680821555 (Maybe a6989586621680821555) -> Type
type Apply (Foldr_6989586621680822439Sym1 a6989586621680822445 :: TyFun b (Maybe a ~> b) -> Type) (a6989586621680822446 :: b) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldr_6989586621680822439Sym1 a6989586621680822445 :: TyFun b (Maybe a ~> b) -> Type) (a6989586621680822446 :: b) = Foldr_6989586621680822439Sym2 a6989586621680822445 a6989586621680822446
type Apply (Foldl_6989586621680822455Sym1 a6989586621680822461 :: TyFun b (Maybe a ~> b) -> Type) (a6989586621680822462 :: b) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl_6989586621680822455Sym1 a6989586621680822461 :: TyFun b (Maybe a ~> b) -> Type) (a6989586621680822462 :: b) = Foldl_6989586621680822455Sym2 a6989586621680822461 a6989586621680822462
type Apply (Lambda_6989586621680700392Sym0 :: TyFun k (TyFun (k1 ~> First a) (TyFun k1 (Maybe a) -> Type) -> Type) -> Type) (a6989586621680700390 :: k) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (Lambda_6989586621680700392Sym0 :: TyFun k (TyFun (k1 ~> First a) (TyFun k1 (Maybe a) -> Type) -> Type) -> Type) (a6989586621680700390 :: k) = Lambda_6989586621680700392Sym1 a6989586621680700390 :: TyFun (k1 ~> First a) (TyFun k1 (Maybe a) -> Type) -> Type
type Apply (Lambda_6989586621680700471Sym0 :: TyFun k (TyFun (k1 ~> Last a) (TyFun k1 (Maybe a) -> Type) -> Type) -> Type) (a6989586621680700469 :: k) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (Lambda_6989586621680700471Sym0 :: TyFun k (TyFun (k1 ~> Last a) (TyFun k1 (Maybe a) -> Type) -> Type) -> Type) (a6989586621680700469 :: k) = Lambda_6989586621680700471Sym1 a6989586621680700469 :: TyFun (k1 ~> Last a) (TyFun k1 (Maybe a) -> Type) -> Type
type Apply (Let6989586621680822283MfSym1 f6989586621680822281 :: TyFun k (TyFun k2 (TyFun (Maybe k3) (Maybe k2) -> Type) -> Type) -> Type) (xs6989586621680822282 :: k) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680822283MfSym1 f6989586621680822281 :: TyFun k (TyFun k2 (TyFun (Maybe k3) (Maybe k2) -> Type) -> Type) -> Type) (xs6989586621680822282 :: k) = Let6989586621680822283MfSym2 f6989586621680822281 xs6989586621680822282
type Apply (Let6989586621680822304MfSym1 f6989586621680822302 :: TyFun k (TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) -> Type) (xs6989586621680822303 :: k) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680822304MfSym1 f6989586621680822302 :: TyFun k (TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) -> Type) (xs6989586621680822303 :: k) = Let6989586621680822304MfSym2 f6989586621680822302 xs6989586621680822303
type Apply (Let6989586621680822283MfSym2 f6989586621680822281 xs6989586621680822282 :: TyFun k2 (TyFun (Maybe k3) (Maybe k2) -> Type) -> Type) (a6989586621680822284 :: k2) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680822283MfSym2 f6989586621680822281 xs6989586621680822282 :: TyFun k2 (TyFun (Maybe k3) (Maybe k2) -> Type) -> Type) (a6989586621680822284 :: k2) = Let6989586621680822283MfSym3 f6989586621680822281 xs6989586621680822282 a6989586621680822284
type Eval (FoldMap f ('Just x) :: a2 -> Type) 
Instance details

Defined in Fcf.Class.Foldable

type Eval (FoldMap f ('Just x) :: a2 -> Type) = Eval (f x)
type Eval (FoldMap f ('Nothing :: Maybe a1) :: a2 -> Type) 
Instance details

Defined in Fcf.Class.Foldable

type Eval (FoldMap f ('Nothing :: Maybe a1) :: a2 -> Type) = MEmpty :: a2
type Eval (Foldr f y ('Just x) :: a2 -> Type) 
Instance details

Defined in Fcf.Class.Foldable

type Eval (Foldr f y ('Just x) :: a2 -> Type) = Eval (f x y)
type Eval (Foldr f y ('Nothing :: Maybe a1) :: a2 -> Type) 
Instance details

Defined in Fcf.Class.Foldable

type Eval (Foldr f y ('Nothing :: Maybe a1) :: a2 -> Type) = y
type Rep (Maybe a) 
Instance details

Defined in GHC.Generics

type Rep (Maybe a) = D1 ('MetaData "Maybe" "GHC.Maybe" "base" 'False) (C1 ('MetaCons "Nothing" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Just" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))
type MEmpty 
Instance details

Defined in Fcf.Class.Monoid

type MEmpty = 'Nothing :: Maybe a
type Index (Maybe a) 
Instance details

Defined in Control.Lens.At

type Index (Maybe a) = ()
type IxValue (Maybe a) 
Instance details

Defined in Control.Lens.At

type IxValue (Maybe a) = a
type Mempty 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Mempty = Mempty_6989586621680690771Sym0 :: Maybe a
type Sing 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = SMaybe :: Maybe a -> Type
type Demote (Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Demote (Maybe a) = Maybe (Demote a)
type Element (Maybe a) 
Instance details

Defined in Universum.Container.Class

type Element (Maybe a) = ElementDefault (Maybe a)
type DemoteRep (Maybe a) 
Instance details

Defined in GHC.Generics

type DemoteRep (Maybe a) = Maybe (DemoteRep a)
data Sing (b :: Maybe a) 
Instance details

Defined in GHC.Generics

data Sing (b :: Maybe a) where
type TypeDocFieldDescriptions (Maybe a) 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type ToT (Maybe a) 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT (Maybe a) = 'TOption (ToT a)
type Rep1 Maybe 
Instance details

Defined in GHC.Generics

type Rep1 Maybe = D1 ('MetaData "Maybe" "GHC.Maybe" "base" 'False) (C1 ('MetaCons "Nothing" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Just" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Mconcat (arg :: [Maybe a]) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Mconcat (arg :: [Maybe a]) = Apply (Mconcat_6989586621680690724Sym0 :: TyFun [Maybe a] (Maybe a) -> Type) arg
type Show_ (arg :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Show

type Show_ (arg :: Maybe a) = Apply (Show__6989586621680636125Sym0 :: TyFun (Maybe a) Symbol -> Type) arg
type Sconcat (arg :: NonEmpty (Maybe a)) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sconcat (arg :: NonEmpty (Maybe a)) = Apply (Sconcat_6989586621680240021Sym0 :: TyFun (NonEmpty (Maybe a)) (Maybe a) -> Type) arg
type Mappend (arg1 :: Maybe a) (arg2 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Mappend (arg1 :: Maybe a) (arg2 :: Maybe a) = Apply (Apply (Mappend_6989586621680690710Sym0 :: TyFun (Maybe a) (Maybe a ~> Maybe a) -> Type) arg1) arg2
type ShowList (arg1 :: [Maybe a]) arg2 
Instance details

Defined in Data.Singletons.Prelude.Show

type ShowList (arg1 :: [Maybe a]) arg2 = Apply (Apply (ShowList_6989586621680636133Sym0 :: TyFun [Maybe a] (Symbol ~> Symbol) -> Type) arg1) arg2
type (a2 :: Maybe a1) <> (a3 :: Maybe a1) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type (a2 :: Maybe a1) <> (a3 :: Maybe a1) = Apply (Apply (TFHelper_6989586621680240170Sym0 :: TyFun (Maybe a1) (Maybe a1 ~> Maybe a1) -> Type) a2) a3
type Empty 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Empty = Empty_6989586621680072416Sym0 :: Maybe a
type Mzero 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Mzero = Mzero_6989586621680011414Sym0 :: Maybe a
type Min (arg1 :: Maybe a) (arg2 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Min (arg1 :: Maybe a) (arg2 :: Maybe a) = Apply (Apply (Min_6989586621679836854Sym0 :: TyFun (Maybe a) (Maybe a ~> Maybe a) -> Type) arg1) arg2
type Max (arg1 :: Maybe a) (arg2 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Max (arg1 :: Maybe a) (arg2 :: Maybe a) = Apply (Apply (Max_6989586621679836838Sym0 :: TyFun (Maybe a) (Maybe a ~> Maybe a) -> Type) arg1) arg2
type (arg1 :: Maybe a) >= (arg2 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type (arg1 :: Maybe a) >= (arg2 :: Maybe a) = Apply (Apply (TFHelper_6989586621679836822Sym0 :: TyFun (Maybe a) (Maybe a ~> Bool) -> Type) arg1) arg2
type (arg1 :: Maybe a) > (arg2 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type (arg1 :: Maybe a) > (arg2 :: Maybe a) = Apply (Apply (TFHelper_6989586621679836806Sym0 :: TyFun (Maybe a) (Maybe a ~> Bool) -> Type) arg1) arg2
type (arg1 :: Maybe a) <= (arg2 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type (arg1 :: Maybe a) <= (arg2 :: Maybe a) = Apply (Apply (TFHelper_6989586621679836790Sym0 :: TyFun (Maybe a) (Maybe a ~> Bool) -> Type) arg1) arg2
type (arg1 :: Maybe a) < (arg2 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type (arg1 :: Maybe a) < (arg2 :: Maybe a) = Apply (Apply (TFHelper_6989586621679836774Sym0 :: TyFun (Maybe a) (Maybe a ~> Bool) -> Type) arg1) arg2
type Compare (a2 :: Maybe a1) (a3 :: Maybe a1) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Compare (a2 :: Maybe a1) (a3 :: Maybe a1) = Apply (Apply (Compare_6989586621679847835Sym0 :: TyFun (Maybe a1) (Maybe a1 ~> Ordering) -> Type) a2) a3
type (x :: Maybe a) /= (y :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Eq

type (x :: Maybe a) /= (y :: Maybe a) = Not (x == y)
type (a2 :: Maybe a1) == (b :: Maybe a1) 
Instance details

Defined in Data.Singletons.Prelude.Eq

type (a2 :: Maybe a1) == (b :: Maybe a1) = Equals_6989586621679819596 a2 b
type HKD Maybe (a :: Type) 
Instance details

Defined in Data.Vinyl.XRec

type HKD Maybe (a :: Type) = Maybe a
type ShowsPrec a2 (a3 :: Maybe a1) a4 
Instance details

Defined in Data.Singletons.Prelude.Show

type ShowsPrec a2 (a3 :: Maybe a1) a4 = Apply (Apply (Apply (ShowsPrec_6989586621680653283Sym0 :: TyFun Nat (Maybe a1 ~> (Symbol ~> Symbol)) -> Type) a2) a3) a4
type Fail a2 
Instance details

Defined in Data.Singletons.Prelude.Monad.Fail

type Fail a2 = Apply (Fail_6989586621680155600Sym0 :: TyFun [Char] (Maybe a1) -> Type) a2
type (a2 :: Maybe a1) <|> (a3 :: Maybe a1) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type (a2 :: Maybe a1) <|> (a3 :: Maybe a1) = Apply (Apply (TFHelper_6989586621680072421Sym0 :: TyFun (Maybe a1) (Maybe a1 ~> Maybe a1) -> Type) a2) a3
type Mplus (arg1 :: Maybe a) (arg2 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Mplus (arg1 :: Maybe a) (arg2 :: Maybe a) = Apply (Apply (Mplus_6989586621680011419Sym0 :: TyFun (Maybe a) (Maybe a ~> Maybe a) -> Type) arg1) arg2
type (a2 :: Maybe a1) <> ('Nothing :: Maybe a1) 
Instance details

Defined in Fcf.Class.Monoid

type (a2 :: Maybe a1) <> ('Nothing :: Maybe a1) = a2
type Apply (FromJustSym0 :: TyFun (Maybe a) a -> Type) (a6989586621679958799 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (FromJustSym0 :: TyFun (Maybe a) a -> Type) (a6989586621679958799 :: Maybe a) = FromJustSym1 a6989586621679958799
type Apply (IsNothingSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679958803 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (IsNothingSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679958803 :: Maybe a) = IsNothingSym1 a6989586621679958803
type Apply (IsJustSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679958806 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (IsJustSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679958806 :: Maybe a) = IsJustSym1 a6989586621679958806
type Apply (FromMaybeSym1 a6989586621679958789 :: TyFun (Maybe a) a -> Type) (a6989586621679958790 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (FromMaybeSym1 a6989586621679958789 :: TyFun (Maybe a) a -> Type) (a6989586621679958790 :: Maybe a) = FromMaybeSym2 a6989586621679958789 a6989586621679958790
type Apply (Compare_6989586621679847835Sym1 a6989586621679847840 :: TyFun (Maybe a) Ordering -> Type) (a6989586621679847841 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Compare_6989586621679847835Sym1 a6989586621679847840 :: TyFun (Maybe a) Ordering -> Type) (a6989586621679847841 :: Maybe a) = Compare_6989586621679847835Sym2 a6989586621679847840 a6989586621679847841
type Apply (FoldMap_6989586621680822423Sym1 a6989586621680822432 :: TyFun (Maybe a) m -> Type) (a6989586621680822433 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldMap_6989586621680822423Sym1 a6989586621680822432 :: TyFun (Maybe a) m -> Type) (a6989586621680822433 :: Maybe a) = FoldMap_6989586621680822423Sym2 a6989586621680822432 a6989586621680822433
type Apply (Maybe_Sym2 a6989586621679957223 a6989586621679957224 :: TyFun (Maybe a) b -> Type) (a6989586621679957225 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (Maybe_Sym2 a6989586621679957223 a6989586621679957224 :: TyFun (Maybe a) b -> Type) (a6989586621679957225 :: Maybe a) = Maybe_Sym3 a6989586621679957223 a6989586621679957224 a6989586621679957225
type Apply (Foldr_6989586621680822439Sym2 a6989586621680822445 a6989586621680822446 :: TyFun (Maybe a) b -> Type) (a6989586621680822447 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldr_6989586621680822439Sym2 a6989586621680822445 a6989586621680822446 :: TyFun (Maybe a) b -> Type) (a6989586621680822447 :: Maybe a) = Foldr_6989586621680822439Sym3 a6989586621680822445 a6989586621680822446 a6989586621680822447
type Apply (Foldl_6989586621680822455Sym2 a6989586621680822461 a6989586621680822462 :: TyFun (Maybe a) b -> Type) (a6989586621680822463 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl_6989586621680822455Sym2 a6989586621680822461 a6989586621680822462 :: TyFun (Maybe a) b -> Type) (a6989586621680822463 :: Maybe a) = Foldl_6989586621680822455Sym3 a6989586621680822461 a6989586621680822462 a6989586621680822463
type ('Nothing :: Maybe a) <> (b :: Maybe a) 
Instance details

Defined in Fcf.Class.Monoid

type ('Nothing :: Maybe a) <> (b :: Maybe a) = b
type Apply (Fail_6989586621680155600Sym0 :: TyFun [Char] (Maybe a) -> Type) (a6989586621680155604 :: [Char]) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Fail

type Apply (Fail_6989586621680155600Sym0 :: TyFun [Char] (Maybe a) -> Type) (a6989586621680155604 :: [Char]) = Fail_6989586621680155600Sym1 a6989586621680155604 :: Maybe a
type Apply (CatMaybesSym0 :: TyFun [Maybe a] [a] -> Type) (a6989586621679958774 :: [Maybe a]) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (CatMaybesSym0 :: TyFun [Maybe a] [a] -> Type) (a6989586621679958774 :: [Maybe a]) = CatMaybesSym1 a6989586621679958774
type Apply (ListToMaybeSym0 :: TyFun [a] (Maybe a) -> Type) (a6989586621679958780 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (ListToMaybeSym0 :: TyFun [a] (Maybe a) -> Type) (a6989586621679958780 :: [a]) = ListToMaybeSym1 a6989586621679958780
type Apply (MaybeToListSym0 :: TyFun (Maybe a) [a] -> Type) (a6989586621679958784 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (MaybeToListSym0 :: TyFun (Maybe a) [a] -> Type) (a6989586621679958784 :: Maybe a) = MaybeToListSym1 a6989586621679958784
type Apply (MaxInternalSym0 :: TyFun (Maybe a) (MaxInternal a) -> Type) (a6989586621680811862 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MaxInternalSym0 :: TyFun (Maybe a) (MaxInternal a) -> Type) (a6989586621680811862 :: Maybe a) = MaxInternalSym1 a6989586621680811862
type Apply (MinInternalSym0 :: TyFun (Maybe a) (MinInternal a) -> Type) (a6989586621680811865 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MinInternalSym0 :: TyFun (Maybe a) (MinInternal a) -> Type) (a6989586621680811865 :: Maybe a) = MinInternalSym1 a6989586621680811865
type Apply (OptionSym0 :: TyFun (Maybe a) (Option a) -> Type) (a6989586621680249373 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply (OptionSym0 :: TyFun (Maybe a) (Option a) -> Type) (a6989586621680249373 :: Maybe a) = OptionSym1 a6989586621680249373
type Apply (FirstSym0 :: TyFun (Maybe a) (First a) -> Type) (a6989586621680694166 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (FirstSym0 :: TyFun (Maybe a) (First a) -> Type) (a6989586621680694166 :: Maybe a) = FirstSym1 a6989586621680694166
type Apply (LastSym0 :: TyFun (Maybe a) (Last a) -> Type) (a6989586621680694193 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (LastSym0 :: TyFun (Maybe a) (Last a) -> Type) (a6989586621680694193 :: Maybe a) = LastSym1 a6989586621680694193
type Apply (GetOptionSym0 :: TyFun (Option a) (Maybe a) -> Type) (a6989586621680249376 :: Option a) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply (GetOptionSym0 :: TyFun (Option a) (Maybe a) -> Type) (a6989586621680249376 :: Option a) = GetOptionSym1 a6989586621680249376
type Apply (GetFirstSym0 :: TyFun (First a) (Maybe a) -> Type) (a6989586621680694169 :: First a) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (GetFirstSym0 :: TyFun (First a) (Maybe a) -> Type) (a6989586621680694169 :: First a) = GetFirstSym1 a6989586621680694169
type Apply (GetLastSym0 :: TyFun (Last a) (Maybe a) -> Type) (a6989586621680694196 :: Last a) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (GetLastSym0 :: TyFun (Last a) (Maybe a) -> Type) (a6989586621680694196 :: Last a) = GetLastSym1 a6989586621680694196
type Apply (GetMaxInternalSym0 :: TyFun (MaxInternal a) (Maybe a) -> Type) (a6989586621680811872 :: MaxInternal a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (GetMaxInternalSym0 :: TyFun (MaxInternal a) (Maybe a) -> Type) (a6989586621680811872 :: MaxInternal a) = GetMaxInternalSym1 a6989586621680811872
type Apply (GetMinInternalSym0 :: TyFun (MinInternal a) (Maybe a) -> Type) (a6989586621680811868 :: MinInternal a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (GetMinInternalSym0 :: TyFun (MinInternal a) (Maybe a) -> Type) (a6989586621680811868 :: MinInternal a) = GetMinInternalSym1 a6989586621680811868
type Apply (FindSym1 a6989586621680379018 :: TyFun [a] (Maybe a) -> Type) (a6989586621680379019 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FindSym1 a6989586621680379018 :: TyFun [a] (Maybe a) -> Type) (a6989586621680379019 :: [a]) = FindSym2 a6989586621680379018 a6989586621680379019
type Apply (FindIndexSym1 a6989586621680378991 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621680378992 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FindIndexSym1 a6989586621680378991 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621680378992 :: [a]) = FindIndexSym2 a6989586621680378991 a6989586621680378992
type Apply (ElemIndexSym1 a6989586621680379009 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621680379010 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ElemIndexSym1 a6989586621680379009 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621680379010 :: [a]) = ElemIndexSym2 a6989586621680379009 a6989586621680379010
type Apply (StripPrefixSym1 a6989586621680498340 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621680498341 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (StripPrefixSym1 a6989586621680498340 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621680498341 :: [a]) = StripPrefixSym2 a6989586621680498340 a6989586621680498341
type Apply (TFHelper_6989586621680072421Sym1 a6989586621680072426 :: TyFun (Maybe a) (Maybe a) -> Type) (a6989586621680072427 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621680072421Sym1 a6989586621680072426 :: TyFun (Maybe a) (Maybe a) -> Type) (a6989586621680072427 :: Maybe a) = TFHelper_6989586621680072421Sym2 a6989586621680072426 a6989586621680072427
type Apply (TFHelper_6989586621680240170Sym1 a6989586621680240175 :: TyFun (Maybe a) (Maybe a) -> Type) (a6989586621680240176 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply (TFHelper_6989586621680240170Sym1 a6989586621680240175 :: TyFun (Maybe a) (Maybe a) -> Type) (a6989586621680240176 :: Maybe a) = TFHelper_6989586621680240170Sym2 a6989586621680240175 a6989586621680240176
type Apply (OptionalSym0 :: TyFun (f a) (f (Maybe a)) -> Type) (a6989586621681492086 :: f a) 
Instance details

Defined in Data.Singletons.Prelude.Applicative

type Apply (OptionalSym0 :: TyFun (f a) (f (Maybe a)) -> Type) (a6989586621681492086 :: f a) = OptionalSym1 a6989586621681492086
type Apply (LookupSym1 a6989586621680378716 :: TyFun [(a, b)] (Maybe b) -> Type) (a6989586621680378717 :: [(a, b)]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (LookupSym1 a6989586621680378716 :: TyFun [(a, b)] (Maybe b) -> Type) (a6989586621680378717 :: [(a, b)]) = LookupSym2 a6989586621680378716 a6989586621680378717
type Apply (Fmap_6989586621680072040Sym1 a6989586621680072045 :: TyFun (Maybe a) (Maybe b) -> Type) (a6989586621680072046 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (Fmap_6989586621680072040Sym1 a6989586621680072045 :: TyFun (Maybe a) (Maybe b) -> Type) (a6989586621680072046 :: Maybe a) = Fmap_6989586621680072040Sym2 a6989586621680072045 a6989586621680072046
type Apply (TFHelper_6989586621680072052Sym1 a6989586621680072057 :: TyFun (Maybe b) (Maybe a) -> Type) (a6989586621680072058 :: Maybe b) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621680072052Sym1 a6989586621680072057 :: TyFun (Maybe b) (Maybe a) -> Type) (a6989586621680072058 :: Maybe b) = TFHelper_6989586621680072052Sym2 a6989586621680072057 a6989586621680072058
type Apply (TFHelper_6989586621680072173Sym1 a6989586621680072178 :: TyFun (Maybe a) (Maybe b) -> Type) (a6989586621680072179 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621680072173Sym1 a6989586621680072178 :: TyFun (Maybe a) (Maybe b) -> Type) (a6989586621680072179 :: Maybe a) = TFHelper_6989586621680072173Sym2 a6989586621680072178 a6989586621680072179
type Apply (TFHelper_6989586621680072200Sym1 a6989586621680072205 :: TyFun (Maybe b) (Maybe b) -> Type) (a6989586621680072206 :: Maybe b) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621680072200Sym1 a6989586621680072205 :: TyFun (Maybe b) (Maybe b) -> Type) (a6989586621680072206 :: Maybe b) = TFHelper_6989586621680072200Sym2 a6989586621680072205 a6989586621680072206
type Apply (TFHelper_6989586621680072345Sym1 a6989586621680072354 :: TyFun (Maybe b) (Maybe b) -> Type) (a6989586621680072355 :: Maybe b) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621680072345Sym1 a6989586621680072354 :: TyFun (Maybe b) (Maybe b) -> Type) (a6989586621680072355 :: Maybe b) = TFHelper_6989586621680072345Sym2 a6989586621680072354 a6989586621680072355
type Apply (FindSym1 a6989586621680821889 :: TyFun (t a) (Maybe a) -> Type) (a6989586621680821890 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FindSym1 a6989586621680821889 :: TyFun (t a) (Maybe a) -> Type) (a6989586621680821890 :: t a) = FindSym2 a6989586621680821889 a6989586621680821890
type Apply (Traverse_6989586621681087642Sym1 a6989586621681087647 :: TyFun (Maybe a) (f (Maybe b)) -> Type) (a6989586621681087648 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Traversable

type Apply (Traverse_6989586621681087642Sym1 a6989586621681087647 :: TyFun (Maybe a) (f (Maybe b)) -> Type) (a6989586621681087648 :: Maybe a) = Traverse_6989586621681087642Sym2 a6989586621681087647 a6989586621681087648
type Apply (LiftA2_6989586621680072186Sym2 a6989586621680072192 a6989586621680072193 :: TyFun (Maybe b) (Maybe c) -> Type) (a6989586621680072194 :: Maybe b) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (LiftA2_6989586621680072186Sym2 a6989586621680072192 a6989586621680072193 :: TyFun (Maybe b) (Maybe c) -> Type) (a6989586621680072194 :: Maybe b) = LiftA2_6989586621680072186Sym3 a6989586621680072192 a6989586621680072193 a6989586621680072194
type Apply (Let6989586621680822283MfSym3 f6989586621680822281 xs6989586621680822282 a6989586621680822284 :: TyFun (Maybe k3) (Maybe k2) -> Type) (a6989586621680822285 :: Maybe k3) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680822283MfSym3 f6989586621680822281 xs6989586621680822282 a6989586621680822284 :: TyFun (Maybe k3) (Maybe k2) -> Type) (a6989586621680822285 :: Maybe k3) = Let6989586621680822283MfSym4 f6989586621680822281 xs6989586621680822282 a6989586621680822284 a6989586621680822285
type Eval (Init '[a2] :: Maybe [a1] -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (Init '[a2] :: Maybe [a1] -> Type) = 'Just ('[] :: [a1])
type Eval (Init ('[] :: [a]) :: Maybe [a] -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (Init ('[] :: [a]) :: Maybe [a] -> Type) = 'Nothing :: Maybe [a]
type Eval (Tail (_a ': as) :: Maybe [a] -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (Tail (_a ': as) :: Maybe [a] -> Type) = 'Just as
type Eval (Tail ('[] :: [a]) :: Maybe [a] -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (Tail ('[] :: [a]) :: Maybe [a] -> Type) = 'Nothing :: Maybe [a]
type Eval (Init (a2 ': (b ': as)) :: Maybe [a1] -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (Init (a2 ': (b ': as)) :: Maybe [a1] -> Type) = Eval ((Map (Cons a2) :: Maybe [a1] -> Maybe [a1] -> Type) =<< Init (b ': as))
type Eval (Head (a2 ': _as) :: Maybe a1 -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (Head (a2 ': _as) :: Maybe a1 -> Type) = 'Just a2
type Eval (Head ('[] :: [a]) :: Maybe a -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (Head ('[] :: [a]) :: Maybe a -> Type) = 'Nothing :: Maybe a
type Eval (Last (a2 ': (b ': as)) :: Maybe a1 -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (Last (a2 ': (b ': as)) :: Maybe a1 -> Type) = Eval (Last (b ': as))
type Eval (Last '[a2] :: Maybe a1 -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (Last '[a2] :: Maybe a1 -> Type) = 'Just a2
type Eval (Last ('[] :: [a]) :: Maybe a -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (Last ('[] :: [a]) :: Maybe a -> Type) = 'Nothing :: Maybe a
type Apply (StripPrefixSym0 :: TyFun [a] ([a] ~> Maybe [a]) -> Type) (a6989586621680498340 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (StripPrefixSym0 :: TyFun [a] ([a] ~> Maybe [a]) -> Type) (a6989586621680498340 :: [a]) = StripPrefixSym1 a6989586621680498340
type Apply (TFHelper_6989586621680072421Sym0 :: TyFun (Maybe a) (Maybe a ~> Maybe a) -> Type) (a6989586621680072426 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621680072421Sym0 :: TyFun (Maybe a) (Maybe a ~> Maybe a) -> Type) (a6989586621680072426 :: Maybe a) = TFHelper_6989586621680072421Sym1 a6989586621680072426
type Apply (Compare_6989586621679847835Sym0 :: TyFun (Maybe a) (Maybe a ~> Ordering) -> Type) (a6989586621679847840 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Compare_6989586621679847835Sym0 :: TyFun (Maybe a) (Maybe a ~> Ordering) -> Type) (a6989586621679847840 :: Maybe a) = Compare_6989586621679847835Sym1 a6989586621679847840
type Apply (TFHelper_6989586621680240170Sym0 :: TyFun (Maybe a) (Maybe a ~> Maybe a) -> Type) (a6989586621680240175 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply (TFHelper_6989586621680240170Sym0 :: TyFun (Maybe a) (Maybe a ~> Maybe a) -> Type) (a6989586621680240175 :: Maybe a) = TFHelper_6989586621680240170Sym1 a6989586621680240175
type ('Just a2 :: Maybe a1) <> ('Just b :: Maybe a1) 
Instance details

Defined in Fcf.Class.Monoid

type ('Just a2 :: Maybe a1) <> ('Just b :: Maybe a1) = 'Just (a2 <> b)
type Apply (ShowsPrec_6989586621680653283Sym1 a6989586621680653293 :: TyFun (Maybe a) (Symbol ~> Symbol) -> Type) (a6989586621680653294 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowsPrec_6989586621680653283Sym1 a6989586621680653293 :: TyFun (Maybe a) (Symbol ~> Symbol) -> Type) (a6989586621680653294 :: Maybe a) = ShowsPrec_6989586621680653283Sym2 a6989586621680653293 a6989586621680653294
type Apply (TFHelper_6989586621680072200Sym0 :: TyFun (Maybe a) (Maybe b ~> Maybe b) -> Type) (a6989586621680072205 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621680072200Sym0 :: TyFun (Maybe a) (Maybe b ~> Maybe b) -> Type) (a6989586621680072205 :: Maybe a) = TFHelper_6989586621680072200Sym1 a6989586621680072205 :: TyFun (Maybe b) (Maybe b) -> Type
type Apply (TFHelper_6989586621680072334Sym0 :: TyFun (Maybe a) ((a ~> Maybe b) ~> Maybe b) -> Type) (a6989586621680072339 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621680072334Sym0 :: TyFun (Maybe a) ((a ~> Maybe b) ~> Maybe b) -> Type) (a6989586621680072339 :: Maybe a) = TFHelper_6989586621680072334Sym1 a6989586621680072339 :: TyFun (a ~> Maybe b) (Maybe b) -> Type
type Apply (TFHelper_6989586621680072345Sym0 :: TyFun (Maybe a) (Maybe b ~> Maybe b) -> Type) (a6989586621680072354 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621680072345Sym0 :: TyFun (Maybe a) (Maybe b ~> Maybe b) -> Type) (a6989586621680072354 :: Maybe a) = TFHelper_6989586621680072345Sym1 a6989586621680072354 :: TyFun (Maybe b) (Maybe b) -> Type
type Apply (TFHelper_6989586621680072173Sym0 :: TyFun (Maybe (a ~> b)) (Maybe a ~> Maybe b) -> Type) (a6989586621680072178 :: Maybe (a ~> b)) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621680072173Sym0 :: TyFun (Maybe (a ~> b)) (Maybe a ~> Maybe b) -> Type) (a6989586621680072178 :: Maybe (a ~> b)) = TFHelper_6989586621680072173Sym1 a6989586621680072178
type Apply (LiftA2_6989586621680072186Sym1 a6989586621680072192 :: TyFun (Maybe a) (Maybe b ~> Maybe c) -> Type) (a6989586621680072193 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (LiftA2_6989586621680072186Sym1 a6989586621680072192 :: TyFun (Maybe a) (Maybe b ~> Maybe c) -> Type) (a6989586621680072193 :: Maybe a) = LiftA2_6989586621680072186Sym2 a6989586621680072192 a6989586621680072193
type Apply (Let6989586621680822304MfSym2 f6989586621680822302 xs6989586621680822303 :: TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) (a6989586621680822305 :: Maybe k2) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680822304MfSym2 f6989586621680822302 xs6989586621680822303 :: TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) (a6989586621680822305 :: Maybe k2) = Let6989586621680822304MfSym3 f6989586621680822302 xs6989586621680822303 a6989586621680822305
type Eval (FindIndex p (a2 ': as) :: Maybe Nat -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (FindIndex p (a2 ': as) :: Maybe Nat -> Type) = Eval (If (Eval (p a2)) (Pure ('Just 0)) ((Map ((+) 1) :: Maybe Nat -> Maybe Nat -> Type) =<< FindIndex p as))
type Eval (FindIndex _p ('[] :: [a]) :: Maybe Nat -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (FindIndex _p ('[] :: [a]) :: Maybe Nat -> Type) = 'Nothing :: Maybe Nat
type Eval (NumIter a s :: Maybe (k, Nat) -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (NumIter a s :: Maybe (k, Nat) -> Type) = If (Eval (s > 0)) ('Just '(a, s - 1)) ('Nothing :: Maybe (k, Nat))
type Eval (Find p (a2 ': as) :: Maybe a1 -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (Find p (a2 ': as) :: Maybe a1 -> Type) = Eval (If (Eval (p a2)) (Pure ('Just a2)) (Find p as))
type Eval (Find _p ('[] :: [a]) :: Maybe a -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (Find _p ('[] :: [a]) :: Maybe a -> Type) = 'Nothing :: Maybe a
type Eval (Lookup a as :: Maybe b -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (Lookup a as :: Maybe b -> Type) = Eval (Map (Snd :: (k, b) -> b -> Type) (Eval (Find ((TyEq a :: k -> Bool -> Type) <=< (Fst :: (k, b) -> k -> Type)) as)))
type Eval (Map f ('Just a3) :: Maybe a2 -> Type) 
Instance details

Defined in Fcf.Class.Functor

type Eval (Map f ('Just a3) :: Maybe a2 -> Type) = 'Just (Eval (f a3))
type Eval (Map f ('Nothing :: Maybe a) :: Maybe b -> Type) 
Instance details

Defined in Fcf.Class.Functor

type Eval (Map f ('Nothing :: Maybe a) :: Maybe b -> Type) = 'Nothing :: Maybe b
type Eval ('Just x <|> _1 :: Maybe a -> Type) 
Instance details

Defined in Util.Fcf

type Eval ('Just x <|> _1 :: Maybe a -> Type) = 'Just x
type Eval (('Nothing :: Maybe a) <|> m :: Maybe a -> Type) 
Instance details

Defined in Util.Fcf

type Eval (('Nothing :: Maybe a) <|> m :: Maybe a -> Type) = m
type Apply (TFHelper_6989586621680072334Sym1 a6989586621680072339 :: TyFun (a ~> Maybe b) (Maybe b) -> Type) (a6989586621680072340 :: a ~> Maybe b) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621680072334Sym1 a6989586621680072339 :: TyFun (a ~> Maybe b) (Maybe b) -> Type) (a6989586621680072340 :: a ~> Maybe b) = TFHelper_6989586621680072334Sym2 a6989586621680072339 a6989586621680072340
type Apply (FindSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe a) -> Type) (a6989586621680379018 :: a ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FindSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe a) -> Type) (a6989586621680379018 :: a ~> Bool) = FindSym1 a6989586621680379018
type Apply (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Nat) -> Type) (a6989586621680378991 :: a ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Nat) -> Type) (a6989586621680378991 :: a ~> Bool) = FindIndexSym1 a6989586621680378991
type Apply (Fmap_6989586621680072040Sym0 :: TyFun (a ~> b) (Maybe a ~> Maybe b) -> Type) (a6989586621680072045 :: a ~> b) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (Fmap_6989586621680072040Sym0 :: TyFun (a ~> b) (Maybe a ~> Maybe b) -> Type) (a6989586621680072045 :: a ~> b) = Fmap_6989586621680072040Sym1 a6989586621680072045
type Apply (MapMaybeSym0 :: TyFun (a ~> Maybe b) ([a] ~> [b]) -> Type) (a6989586621679958759 :: a ~> Maybe b) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (MapMaybeSym0 :: TyFun (a ~> Maybe b) ([a] ~> [b]) -> Type) (a6989586621679958759 :: a ~> Maybe b) = MapMaybeSym1 a6989586621679958759
type Apply (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) (a6989586621680379408 :: b ~> Maybe (a, b)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) (a6989586621680379408 :: b ~> Maybe (a, b)) = UnfoldrSym1 a6989586621680379408
type Apply (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) (a6989586621680821889 :: a ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) (a6989586621680821889 :: a ~> Bool) = FindSym1 a6989586621680821889 :: TyFun (t a) (Maybe a) -> Type
type Apply (FoldMap_6989586621680822423Sym0 :: TyFun (a ~> m) (Maybe a ~> m) -> Type) (a6989586621680822432 :: a ~> m) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FoldMap_6989586621680822423Sym0 :: TyFun (a ~> m) (Maybe a ~> m) -> Type) (a6989586621680822432 :: a ~> m) = FoldMap_6989586621680822423Sym1 a6989586621680822432
type Apply (Foldr_6989586621680822439Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (Maybe a ~> b)) -> Type) (a6989586621680822445 :: a ~> (b ~> b)) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldr_6989586621680822439Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (Maybe a ~> b)) -> Type) (a6989586621680822445 :: a ~> (b ~> b)) = Foldr_6989586621680822439Sym1 a6989586621680822445
type Apply (Foldl_6989586621680822455Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (Maybe a ~> b)) -> Type) (a6989586621680822461 :: b ~> (a ~> b)) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Foldl_6989586621680822455Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (Maybe a ~> b)) -> Type) (a6989586621680822461 :: b ~> (a ~> b)) = Foldl_6989586621680822455Sym1 a6989586621680822461
type Apply (Traverse_6989586621681087642Sym0 :: TyFun (a ~> f b) (Maybe a ~> f (Maybe b)) -> Type) (a6989586621681087647 :: a ~> f b) 
Instance details

Defined in Data.Singletons.Prelude.Traversable

type Apply (Traverse_6989586621681087642Sym0 :: TyFun (a ~> f b) (Maybe a ~> f (Maybe b)) -> Type) (a6989586621681087647 :: a ~> f b) = Traverse_6989586621681087642Sym1 a6989586621681087647
type Apply (LiftA2_6989586621680072186Sym0 :: TyFun (a ~> (b ~> c)) (Maybe a ~> (Maybe b ~> Maybe c)) -> Type) (a6989586621680072192 :: a ~> (b ~> c)) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (LiftA2_6989586621680072186Sym0 :: TyFun (a ~> (b ~> c)) (Maybe a ~> (Maybe b ~> Maybe c)) -> Type) (a6989586621680072192 :: a ~> (b ~> c)) = LiftA2_6989586621680072186Sym1 a6989586621680072192
type Apply (Maybe_Sym1 a6989586621679957223 :: TyFun (a ~> b) (Maybe a ~> b) -> Type) (a6989586621679957224 :: a ~> b) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (Maybe_Sym1 a6989586621679957223 :: TyFun (a ~> b) (Maybe a ~> b) -> Type) (a6989586621679957224 :: a ~> b) = Maybe_Sym2 a6989586621679957223 a6989586621679957224
type Apply (Let6989586621679958764RsSym0 :: TyFun (a ~> Maybe k1) (TyFun k (TyFun [a] [k1] -> Type) -> Type) -> Type) (f6989586621679958761 :: a ~> Maybe k1) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (Let6989586621679958764RsSym0 :: TyFun (a ~> Maybe k1) (TyFun k (TyFun [a] [k1] -> Type) -> Type) -> Type) (f6989586621679958761 :: a ~> Maybe k1) = Let6989586621679958764RsSym1 f6989586621679958761 :: TyFun k (TyFun [a] [k1] -> Type) -> Type
type Apply (Let6989586621680822283MfSym0 :: TyFun (k2 ~> (k3 ~> k2)) (TyFun k (TyFun k2 (TyFun (Maybe k3) (Maybe k2) -> Type) -> Type) -> Type) -> Type) (f6989586621680822281 :: k2 ~> (k3 ~> k2)) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680822283MfSym0 :: TyFun (k2 ~> (k3 ~> k2)) (TyFun k (TyFun k2 (TyFun (Maybe k3) (Maybe k2) -> Type) -> Type) -> Type) -> Type) (f6989586621680822281 :: k2 ~> (k3 ~> k2)) = Let6989586621680822283MfSym1 f6989586621680822281 :: TyFun k (TyFun k2 (TyFun (Maybe k3) (Maybe k2) -> Type) -> Type) -> Type
type Apply (Let6989586621680822304MfSym0 :: TyFun (k2 ~> (k3 ~> k3)) (TyFun k (TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) -> Type) -> Type) (f6989586621680822302 :: k2 ~> (k3 ~> k3)) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680822304MfSym0 :: TyFun (k2 ~> (k3 ~> k3)) (TyFun k (TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) -> Type) -> Type) (f6989586621680822302 :: k2 ~> (k3 ~> k3)) = Let6989586621680822304MfSym1 f6989586621680822302 :: TyFun k (TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621680700392Sym1 a6989586621680700390 :: TyFun (k1 ~> First a) (TyFun k1 (Maybe a) -> Type) -> Type) (k6989586621680700391 :: k1 ~> First a) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (Lambda_6989586621680700392Sym1 a6989586621680700390 :: TyFun (k1 ~> First a) (TyFun k1 (Maybe a) -> Type) -> Type) (k6989586621680700391 :: k1 ~> First a) = Lambda_6989586621680700392Sym2 a6989586621680700390 k6989586621680700391
type Apply (Lambda_6989586621680700471Sym1 a6989586621680700469 :: TyFun (k1 ~> Last a) (TyFun k1 (Maybe a) -> Type) -> Type) (k6989586621680700470 :: k1 ~> Last a) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (Lambda_6989586621680700471Sym1 a6989586621680700469 :: TyFun (k1 ~> Last a) (TyFun k1 (Maybe a) -> Type) -> Type) (k6989586621680700470 :: k1 ~> Last a) = Lambda_6989586621680700471Sym2 a6989586621680700469 k6989586621680700470
type ToT (NamedF Maybe a name) 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT (NamedF Maybe a name) = ToT (Maybe a)
type Unwrappable (NamedF Maybe a name) Source # 
Instance details

Defined in Lorentz.Wrappable

type Unwrappable (NamedF Maybe a name) = Maybe a

type List = [] Source #

data ContractRef arg #

Instances

Instances details
cp ~ cp' => FromContractRef cp (ContractRef cp') Source # 
Instance details

Defined in Lorentz.Address

cp ~ cp' => ToContractRef cp (ContractRef cp') Source # 
Instance details

Defined in Lorentz.Address

Eq (ContractRef arg) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Methods

(==) :: ContractRef arg -> ContractRef arg -> Bool #

(/=) :: ContractRef arg -> ContractRef arg -> Bool #

Show (ContractRef arg) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Methods

showsPrec :: Int -> ContractRef arg -> ShowS #

show :: ContractRef arg -> String #

showList :: [ContractRef arg] -> ShowS #

WellTypedToT arg => Buildable (ContractRef arg) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Methods

build :: ContractRef arg -> Builder #

PolyTypeHasDocC '[cp] => TypeHasDoc (ContractRef cp) 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions (ContractRef cp) :: FieldDescriptions #

WellTypedToT arg => IsoValue (ContractRef arg) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (ContractRef arg) :: T #

Methods

toVal :: ContractRef arg -> Value (ToT (ContractRef arg)) #

fromVal :: Value (ToT (ContractRef arg)) -> ContractRef arg #

HasAnnotation a => HasAnnotation (ContractRef a) Source # 
Instance details

Defined in Lorentz.Annotation

ToAddress (ContractRef cp) Source # 
Instance details

Defined in Lorentz.Address

CanCastTo a1 a2 => CanCastTo (ContractRef a1 :: Type) (ContractRef a2 :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (ContractRef a1) -> Proxy (ContractRef a2) -> () Source #

type TypeDocFieldDescriptions (ContractRef cp) 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type ToT (ContractRef arg) 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT (ContractRef arg) = 'TContract (ToT arg)

newtype TAddress p Source #

Address which remembers the parameter type of the contract it refers to.

It differs from Michelson's contract type because it cannot contain entrypoint, and it always refers to entire contract parameter even if this contract has explicit default entrypoint.

Constructors

TAddress 

Fields

Instances

Instances details
(FailWhen cond msg, cond ~ (CanHaveEntrypoints cp && Not (ParameterEntrypointsDerivation cp == EpdNone)), msg ~ (((('Text "Cannot apply `ToContractRef` to `TAddress`" :$$: 'Text "Consider using call(Def)TAddress first`") :$$: 'Text "(or if you know your parameter type is primitive,") :$$: 'Text " make sure typechecker also knows about that)") :$$: (('Text "For parameter `" :<>: 'ShowType cp) :<>: 'Text "`")), cp ~ arg, NiceParameter arg, NiceParameterFull cp, GetDefaultEntrypointArg cp ~ cp) => ToContractRef arg (TAddress cp) Source # 
Instance details

Defined in Lorentz.Address

cp ~ cp' => ToTAddress cp (TAddress cp') Source # 
Instance details

Defined in Lorentz.Address

Methods

toTAddress :: TAddress cp' -> TAddress cp Source #

CanCastTo Address (TAddress p :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy Address -> Proxy (TAddress p) -> () Source #

CanCastTo (TAddress p :: Type) Address Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (TAddress p) -> Proxy Address -> () Source #

Eq (TAddress p) Source # 
Instance details

Defined in Lorentz.Address

Methods

(==) :: TAddress p -> TAddress p -> Bool #

(/=) :: TAddress p -> TAddress p -> Bool #

Ord (TAddress p) Source # 
Instance details

Defined in Lorentz.Address

Methods

compare :: TAddress p -> TAddress p -> Ordering #

(<) :: TAddress p -> TAddress p -> Bool #

(<=) :: TAddress p -> TAddress p -> Bool #

(>) :: TAddress p -> TAddress p -> Bool #

(>=) :: TAddress p -> TAddress p -> Bool #

max :: TAddress p -> TAddress p -> TAddress p #

min :: TAddress p -> TAddress p -> TAddress p #

Show (TAddress p) Source # 
Instance details

Defined in Lorentz.Address

Methods

showsPrec :: Int -> TAddress p -> ShowS #

show :: TAddress p -> String #

showList :: [TAddress p] -> ShowS #

Generic (TAddress p) Source # 
Instance details

Defined in Lorentz.Address

Associated Types

type Rep (TAddress p) :: Type -> Type #

Methods

from :: TAddress p -> Rep (TAddress p) x #

to :: Rep (TAddress p) x -> TAddress p #

Buildable (TAddress p) Source # 
Instance details

Defined in Lorentz.Address

Methods

build :: TAddress p -> Builder #

TypeHasDoc p => TypeHasDoc (TAddress p) Source # 
Instance details

Defined in Lorentz.Doc

Associated Types

type TypeDocFieldDescriptions (TAddress p) :: FieldDescriptions #

IsoValue (TAddress p) Source # 
Instance details

Defined in Lorentz.Address

Associated Types

type ToT (TAddress p) :: T #

Methods

toVal :: TAddress p -> Value (ToT (TAddress p)) #

fromVal :: Value (ToT (TAddress p)) -> TAddress p #

HasAnnotation (TAddress p) Source # 
Instance details

Defined in Lorentz.Address

ToAddress (TAddress cp) Source # 
Instance details

Defined in Lorentz.Address

type Rep (TAddress p) Source # 
Instance details

Defined in Lorentz.Address

type Rep (TAddress p) = D1 ('MetaData "TAddress" "Lorentz.Address" "lorentz-0.11.0-inplace" 'True) (C1 ('MetaCons "TAddress" 'PrefixI 'True) (S1 ('MetaSel ('Just "unTAddress") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Address)))
type TypeDocFieldDescriptions (TAddress p) Source # 
Instance details

Defined in Lorentz.Doc

type ToT (TAddress p) Source # 
Instance details

Defined in Lorentz.Address

type ToT (TAddress p) = GValueType (Rep (TAddress p))

newtype FutureContract arg Source #

Address associated with value of contract arg type.

Places where ContractRef can appear are now severely limited, this type gives you type-safety of ContractRef but still can be used everywhere. This type is not a full-featured one rather a helper; in particular, once pushing it on stack, you cannot return it back to Haskell world.

Note that it refers to an entrypoint of the contract, not just the contract as a whole. In this sense this type differs from TAddress.

Unlike with ContractRef, having this type you still cannot be sure that the referred contract exists and need to perform a lookup before calling it.

Constructors

FutureContract 

Instances

Instances details
cp ~ cp' => FromContractRef cp (FutureContract cp') Source # 
Instance details

Defined in Lorentz.Address

(NiceParameter cp, cp ~ cp') => ToContractRef cp (FutureContract cp') Source # 
Instance details

Defined in Lorentz.Address

TypeHasDoc p => TypeHasDoc (FutureContract p) Source # 
Instance details

Defined in Lorentz.Doc

Associated Types

type TypeDocFieldDescriptions (FutureContract p) :: FieldDescriptions #

IsoValue (FutureContract arg) Source # 
Instance details

Defined in Lorentz.Address

Associated Types

type ToT (FutureContract arg) :: T #

HasAnnotation (FutureContract a) Source # 
Instance details

Defined in Lorentz.Address

ToAddress (FutureContract cp) Source # 
Instance details

Defined in Lorentz.Address

CanCastTo (FutureContract p :: Type) EpAddress Source # 
Instance details

Defined in Lorentz.Coercions

type TypeDocFieldDescriptions (FutureContract p) Source # 
Instance details

Defined in Lorentz.Doc

type ToT (FutureContract arg) Source # 
Instance details

Defined in Lorentz.Address

data EpName #

Instances

Instances details
Eq EpName 
Instance details

Defined in Michelson.Untyped.Entrypoints

Methods

(==) :: EpName -> EpName -> Bool #

(/=) :: EpName -> EpName -> Bool #

Ord EpName 
Instance details

Defined in Michelson.Untyped.Entrypoints

Show EpName 
Instance details

Defined in Michelson.Untyped.Entrypoints

Generic EpName 
Instance details

Defined in Michelson.Untyped.Entrypoints

Associated Types

type Rep EpName :: Type -> Type #

Methods

from :: EpName -> Rep EpName x #

to :: Rep EpName x -> EpName #

ToJSON EpName 
Instance details

Defined in Michelson.Untyped.Entrypoints

FromJSON EpName 
Instance details

Defined in Michelson.Untyped.Entrypoints

NFData EpName 
Instance details

Defined in Michelson.Untyped.Entrypoints

Methods

rnf :: EpName -> () #

Buildable EpName 
Instance details

Defined in Michelson.Untyped.Entrypoints

Methods

build :: EpName -> Builder #

HasCLReader EpName 
Instance details

Defined in Michelson.Untyped.Entrypoints

type Rep EpName 
Instance details

Defined in Michelson.Untyped.Entrypoints

type Rep EpName = D1 ('MetaData "EpName" "Michelson.Untyped.Entrypoints" "morley-1.14.0-inplace" 'True) (C1 ('MetaCons "EpNameUnsafe" 'PrefixI 'True) (S1 ('MetaSel ('Just "unEpName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

pattern DefEpName :: EpName #

type EntrypointCall param arg = EntrypointCallT (ToT param) (ToT arg) #

type SomeEntrypointCall arg = SomeEntrypointCallT (ToT arg) #

Constructors

Conversions

callingTAddress :: forall cp mname. NiceParameterFull cp => TAddress cp -> EntrypointRef mname -> ContractRef (GetEntrypointArgCustom cp mname) Source #

Turn TAddress to ContractRef in Haskell world.

This is an analogy of address to contract convertion in Michelson world, thus you have to supply an entrypoint (or call the default one explicitly).

callingDefTAddress :: forall cp. NiceParameterFull cp => TAddress cp -> ContractRef (GetDefaultEntrypointArg cp) Source #

Specification of callTAddress to call the default entrypoint.

class ToAddress a where Source #

Convert something to Address in Haskell world.

Use this when you want to access state of the contract and are not interested in calling it.

Methods

toAddress :: a -> Address Source #

Instances

Instances details
ToAddress EpAddress Source # 
Instance details

Defined in Lorentz.Address

ToAddress Address Source # 
Instance details

Defined in Lorentz.Address

ToAddress (ContractRef cp) Source # 
Instance details

Defined in Lorentz.Address

ToAddress (FutureContract cp) Source # 
Instance details

Defined in Lorentz.Address

ToAddress (TAddress cp) Source # 
Instance details

Defined in Lorentz.Address

class ToTAddress (cp :: Type) (a :: Type) where Source #

Convert something referring to a contract (not specific entrypoint) to TAddress in Haskell world.

Methods

toTAddress :: a -> TAddress cp Source #

Instances

Instances details
ToTAddress cp Address Source # 
Instance details

Defined in Lorentz.Address

cp ~ cp' => ToTAddress cp (TAddress cp') Source # 
Instance details

Defined in Lorentz.Address

Methods

toTAddress :: TAddress cp' -> TAddress cp Source #

class ToContractRef (cp :: Type) (contract :: Type) where Source #

Convert something to ContractRef in Haskell world.

Methods

toContractRef :: HasCallStack => contract -> ContractRef cp Source #

Instances

Instances details
(NiceParameter cp, cp ~ cp') => ToContractRef cp (FutureContract cp') Source # 
Instance details

Defined in Lorentz.Address

cp ~ cp' => ToContractRef cp (ContractRef cp') Source # 
Instance details

Defined in Lorentz.Address

(FailWhen cond msg, cond ~ (CanHaveEntrypoints cp && Not (ParameterEntrypointsDerivation cp == EpdNone)), msg ~ (((('Text "Cannot apply `ToContractRef` to `TAddress`" :$$: 'Text "Consider using call(Def)TAddress first`") :$$: 'Text "(or if you know your parameter type is primitive,") :$$: 'Text " make sure typechecker also knows about that)") :$$: (('Text "For parameter `" :<>: 'ShowType cp) :<>: 'Text "`")), cp ~ arg, NiceParameter arg, NiceParameterFull cp, GetDefaultEntrypointArg cp ~ cp) => ToContractRef arg (TAddress cp) Source # 
Instance details

Defined in Lorentz.Address

class FromContractRef (cp :: Type) (contract :: Type) where Source #

Convert something from ContractAddr in Haskell world.

Methods

fromContractRef :: ContractRef cp -> contract Source #

Instances

Instances details
FromContractRef cp Address Source # 
Instance details

Defined in Lorentz.Address

FromContractRef cp EpAddress Source # 
Instance details

Defined in Lorentz.Address

cp ~ cp' => FromContractRef cp (FutureContract cp') Source # 
Instance details

Defined in Lorentz.Address

cp ~ cp' => FromContractRef cp (ContractRef cp') Source # 
Instance details

Defined in Lorentz.Address

convertContractRef :: forall cp contract2 contract1. (ToContractRef cp contract1, FromContractRef cp contract2) => contract1 -> contract2 Source #

Misc

class Show a #

Conversion of values to readable Strings.

Derived instances of Show have the following properties, which are compatible with derived instances of Read:

  • The result of show is a syntactically correct Haskell expression containing only constants, given the fixity declarations in force at the point where the type is declared. It contains only the constructor names defined in the data type, parentheses, and spaces. When labelled constructor fields are used, braces, commas, field names, and equal signs are also used.
  • If the constructor is defined to be an infix operator, then showsPrec will produce infix applications of the constructor.
  • the representation will be enclosed in parentheses if the precedence of the top-level constructor in x is less than d (associativity is ignored). Thus, if d is 0 then the result is never surrounded in parentheses; if d is 11 it is always surrounded in parentheses, unless it is an atomic expression.
  • If the constructor is defined using record syntax, then show will produce the record-syntax form, with the fields given in the same order as the original declaration.

For example, given the declarations

infixr 5 :^:
data Tree a =  Leaf a  |  Tree a :^: Tree a

the derived instance of Show is equivalent to

instance (Show a) => Show (Tree a) where

       showsPrec d (Leaf m) = showParen (d > app_prec) $
            showString "Leaf " . showsPrec (app_prec+1) m
         where app_prec = 10

       showsPrec d (u :^: v) = showParen (d > up_prec) $
            showsPrec (up_prec+1) u .
            showString " :^: "      .
            showsPrec (up_prec+1) v
         where up_prec = 5

Note that right-associativity of :^: is ignored. For example,

  • show (Leaf 1 :^: Leaf 2 :^: Leaf 3) produces the string "Leaf 1 :^: (Leaf 2 :^: Leaf 3)".

Minimal complete definition

showsPrec | show

Instances

Instances details
Show Bool

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> Bool -> ShowS #

show :: Bool -> String #

showList :: [Bool] -> ShowS #

Show Char

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> Char -> ShowS #

show :: Char -> String #

showList :: [Char] -> ShowS #

Show Int

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> Int -> ShowS #

show :: Int -> String #

showList :: [Int] -> ShowS #

Show Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

showsPrec :: Int -> Int8 -> ShowS #

show :: Int8 -> String #

showList :: [Int8] -> ShowS #

Show Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

showsPrec :: Int -> Int16 -> ShowS #

show :: Int16 -> String #

showList :: [Int16] -> ShowS #

Show Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

showsPrec :: Int -> Int32 -> ShowS #

show :: Int32 -> String #

showList :: [Int32] -> ShowS #

Show Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

showsPrec :: Int -> Int64 -> ShowS #

show :: Int64 -> String #

showList :: [Int64] -> ShowS #

Show Integer

Since: base-2.1

Instance details

Defined in GHC.Show

Show Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Show

Show Ordering

Since: base-2.1

Instance details

Defined in GHC.Show

Show Word

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> Word -> ShowS #

show :: Word -> String #

showList :: [Word] -> ShowS #

Show Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

showsPrec :: Int -> Word8 -> ShowS #

show :: Word8 -> String #

showList :: [Word8] -> ShowS #

Show Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Show Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Show Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Show RuntimeRep

Since: base-4.11.0.0

Instance details

Defined in GHC.Show

Show VecCount

Since: base-4.11.0.0

Instance details

Defined in GHC.Show

Show VecElem

Since: base-4.11.0.0

Instance details

Defined in GHC.Show

Show CallStack

Since: base-4.9.0.0

Instance details

Defined in GHC.Show

Show SomeTypeRep

Since: base-4.10.0.0

Instance details

Defined in Data.Typeable.Internal

Show Exp 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Exp -> ShowS #

show :: Exp -> String #

showList :: [Exp] -> ShowS #

Show Match 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Match -> ShowS #

show :: Match -> String #

showList :: [Match] -> ShowS #

Show Clause 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Pat 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Pat -> ShowS #

show :: Pat -> String #

showList :: [Pat] -> ShowS #

Show Type 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

Show Dec 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Dec -> ShowS #

show :: Dec -> String #

showList :: [Dec] -> ShowS #

Show Name 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

Show FunDep 
Instance details

Defined in Language.Haskell.TH.Syntax

Show InjectivityAnn 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Overlap 
Instance details

Defined in Language.Haskell.TH.Syntax

Show ()

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> () -> ShowS #

show :: () -> String #

showList :: [()] -> ShowS #

Show TyCon

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> TyCon -> ShowS #

show :: TyCon -> String #

showList :: [TyCon] -> ShowS #

Show Module

Since: base-4.9.0.0

Instance details

Defined in GHC.Show

Show TrName

Since: base-4.9.0.0

Instance details

Defined in GHC.Show

Show KindRep 
Instance details

Defined in GHC.Show

Show TypeLitSort

Since: base-4.11.0.0

Instance details

Defined in GHC.Show

Show Version

Since: base-2.1

Instance details

Defined in Data.Version

Show ByteString 
Instance details

Defined in Data.ByteString.Internal

Show ByteString 
Instance details

Defined in Data.ByteString.Lazy.Internal

Show Builder 
Instance details

Defined in Data.Text.Internal.Builder

Show Scientific

See formatScientific if you need more control over the rendering.

Instance details

Defined in Data.Scientific

Show JSONPathElement 
Instance details

Defined in Data.Aeson.Types.Internal

Show Value 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

Show DotNetTime 
Instance details

Defined in Data.Aeson.Types.Internal

Show Options 
Instance details

Defined in Data.Aeson.Types.Internal

Show SumEncoding 
Instance details

Defined in Data.Aeson.Types.Internal

Show Handle

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Handle.Types

Show ThreadId

Since: base-4.2.0.0

Instance details

Defined in GHC.Conc.Sync

Show Pos 
Instance details

Defined in Data.Attoparsec.Internal.Types

Methods

showsPrec :: Int -> Pos -> ShowS #

show :: Pos -> String #

showList :: [Pos] -> ShowS #

Show More 
Instance details

Defined in Data.Attoparsec.Internal.Types

Methods

showsPrec :: Int -> More -> ShowS #

show :: More -> String #

showList :: [More] -> ShowS #

Show Void

Since: base-4.8.0.0

Instance details

Defined in Data.Void

Methods

showsPrec :: Int -> Void -> ShowS #

show :: Void -> String #

showList :: [Void] -> ShowS #

Show BlockReason

Since: base-4.3.0.0

Instance details

Defined in GHC.Conc.Sync

Show ThreadStatus

Since: base-4.3.0.0

Instance details

Defined in GHC.Conc.Sync

Show BlockedIndefinitelyOnMVar

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show BlockedIndefinitelyOnSTM

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show Deadlock

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show AllocationLimitExceeded

Since: base-4.7.1.0

Instance details

Defined in GHC.IO.Exception

Show CompactionFailed

Since: base-4.10.0.0

Instance details

Defined in GHC.IO.Exception

Show AssertionFailed

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show SomeAsyncException

Since: base-4.7.0.0

Instance details

Defined in GHC.IO.Exception

Show AsyncException

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show ArrayException

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show FixIOException

Since: base-4.11.0.0

Instance details

Defined in GHC.IO.Exception

Show ExitCode 
Instance details

Defined in GHC.IO.Exception

Show IOErrorType

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show HandleType

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Handle.Types

Show BufferMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.Handle.Types

Show Newline

Since: base-4.3.0.0

Instance details

Defined in GHC.IO.Handle.Types

Show NewlineMode

Since: base-4.3.0.0

Instance details

Defined in GHC.IO.Handle.Types

Show MaskingState

Since: base-4.3.0.0

Instance details

Defined in GHC.IO

Show IOException

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show ArithException

Since: base-4.0.0.0

Instance details

Defined in GHC.Exception.Type

Show All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

showsPrec :: Int -> All -> ShowS #

show :: All -> String #

showList :: [All] -> ShowS #

Show Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

showsPrec :: Int -> Any -> ShowS #

show :: Any -> String #

showList :: [Any] -> ShowS #

Show Fixity

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Show Associativity

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Show SourceUnpackedness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Show SourceStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Show DecidedStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Show SomeSymbol

Since: base-4.7.0.0

Instance details

Defined in GHC.TypeLits

Show SomeNat

Since: base-4.7.0.0

Instance details

Defined in GHC.TypeNats

Show IOMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.IOMode

Show GeneralCategory

Since: base-2.1

Instance details

Defined in GHC.Unicode

Show SrcLoc

Since: base-4.9.0.0

Instance details

Defined in GHC.Show

Show SomeException

Since: base-3.0

Instance details

Defined in GHC.Exception.Type

Show Alphabet 
Instance details

Defined in Data.ByteString.Base58.Internal

Show ASCII7_Invalid 
Instance details

Defined in Basement.String.Encoding.ASCII7

Methods

showsPrec :: Int -> ASCII7_Invalid -> ShowS #

show :: ASCII7_Invalid -> String #

showList :: [ASCII7_Invalid] -> ShowS #

Show ISO_8859_1_Invalid 
Instance details

Defined in Basement.String.Encoding.ISO_8859_1

Methods

showsPrec :: Int -> ISO_8859_1_Invalid -> ShowS #

show :: ISO_8859_1_Invalid -> String #

showList :: [ISO_8859_1_Invalid] -> ShowS #

Show UTF16_Invalid 
Instance details

Defined in Basement.String.Encoding.UTF16

Methods

showsPrec :: Int -> UTF16_Invalid -> ShowS #

show :: UTF16_Invalid -> String #

showList :: [UTF16_Invalid] -> ShowS #

Show UTF32_Invalid 
Instance details

Defined in Basement.String.Encoding.UTF32

Methods

showsPrec :: Int -> UTF32_Invalid -> ShowS #

show :: UTF32_Invalid -> String #

showList :: [UTF32_Invalid] -> ShowS #

Show Encoding 
Instance details

Defined in Basement.String

Show String 
Instance details

Defined in Basement.UTF8.Base

Show FileSize 
Instance details

Defined in Basement.Types.OffsetSize

Show ShortByteString 
Instance details

Defined in Data.ByteString.Short.Internal

Show WithInternals 
Instance details

Defined in Data.Bit.Internal

Methods

showsPrec :: Int -> WithInternals -> ShowS #

show :: WithInternals -> String #

showList :: [WithInternals] -> ShowS #

Show F2Poly 
Instance details

Defined in Data.Bit.F2Poly

Show Bit 
Instance details

Defined in Data.Bit.Internal

Methods

showsPrec :: Int -> Bit -> ShowS #

show :: Bit -> String #

showList :: [Bit] -> ShowS #

Show Clock 
Instance details

Defined in System.Clock

Methods

showsPrec :: Int -> Clock -> ShowS #

show :: Clock -> String #

showList :: [Clock] -> ShowS #

Show TimeSpec 
Instance details

Defined in System.Clock

Show IntSet 
Instance details

Defined in Data.IntSet.Internal

Show Bytes 
Instance details

Defined in Data.ByteArray.Bytes

Methods

showsPrec :: Int -> Bytes -> ShowS #

show :: Bytes -> String #

showList :: [Bytes] -> ShowS #

Show Signature 
Instance details

Defined in Crypto.PubKey.ECC.ECDSA

Show PrivateKey 
Instance details

Defined in Crypto.PubKey.ECC.ECDSA

Show PublicKey 
Instance details

Defined in Crypto.PubKey.ECC.ECDSA

Show KeyPair 
Instance details

Defined in Crypto.PubKey.ECC.ECDSA

Show SecretKey 
Instance details

Defined in Crypto.PubKey.Ed25519

Show PublicKey 
Instance details

Defined in Crypto.PubKey.Ed25519

Show Signature 
Instance details

Defined in Crypto.PubKey.Ed25519

Show Blake2b_160 
Instance details

Defined in Crypto.Hash.Blake2b

Show Blake2b_224 
Instance details

Defined in Crypto.Hash.Blake2b

Show Blake2b_256 
Instance details

Defined in Crypto.Hash.Blake2b

Show Blake2b_384 
Instance details

Defined in Crypto.Hash.Blake2b

Show Blake2b_512 
Instance details

Defined in Crypto.Hash.Blake2b

Show Blake2bp_512 
Instance details

Defined in Crypto.Hash.Blake2bp

Show Blake2s_160 
Instance details

Defined in Crypto.Hash.Blake2s

Show Blake2s_224 
Instance details

Defined in Crypto.Hash.Blake2s

Show Blake2s_256 
Instance details

Defined in Crypto.Hash.Blake2s

Show Blake2sp_224 
Instance details

Defined in Crypto.Hash.Blake2sp

Show Blake2sp_256 
Instance details

Defined in Crypto.Hash.Blake2sp

Show Keccak_224 
Instance details

Defined in Crypto.Hash.Keccak

Show Keccak_256 
Instance details

Defined in Crypto.Hash.Keccak

Show Keccak_384 
Instance details

Defined in Crypto.Hash.Keccak

Show Keccak_512 
Instance details

Defined in Crypto.Hash.Keccak

Show MD2 
Instance details

Defined in Crypto.Hash.MD2

Methods

showsPrec :: Int -> MD2 -> ShowS #

show :: MD2 -> String #

showList :: [MD2] -> ShowS #

Show MD4 
Instance details

Defined in Crypto.Hash.MD4

Methods

showsPrec :: Int -> MD4 -> ShowS #

show :: MD4 -> String #

showList :: [MD4] -> ShowS #

Show MD5 
Instance details

Defined in Crypto.Hash.MD5

Methods

showsPrec :: Int -> MD5 -> ShowS #

show :: MD5 -> String #

showList :: [MD5] -> ShowS #

Show RIPEMD160 
Instance details

Defined in Crypto.Hash.RIPEMD160

Show SHA1 
Instance details

Defined in Crypto.Hash.SHA1

Methods

showsPrec :: Int -> SHA1 -> ShowS #

show :: SHA1 -> String #

showList :: [SHA1] -> ShowS #

Show SHA224 
Instance details

Defined in Crypto.Hash.SHA224

Show SHA256 
Instance details

Defined in Crypto.Hash.SHA256

Show SHA3_224 
Instance details

Defined in Crypto.Hash.SHA3

Show SHA3_256 
Instance details

Defined in Crypto.Hash.SHA3

Show SHA3_384 
Instance details

Defined in Crypto.Hash.SHA3

Show SHA3_512 
Instance details

Defined in Crypto.Hash.SHA3

Show SHA384 
Instance details

Defined in Crypto.Hash.SHA384

Show SHA512 
Instance details

Defined in Crypto.Hash.SHA512

Show SHA512t_224 
Instance details

Defined in Crypto.Hash.SHA512t

Show SHA512t_256 
Instance details

Defined in Crypto.Hash.SHA512t

Show Skein256_224 
Instance details

Defined in Crypto.Hash.Skein256

Show Skein256_256 
Instance details

Defined in Crypto.Hash.Skein256

Show Skein512_224 
Instance details

Defined in Crypto.Hash.Skein512

Show Skein512_256 
Instance details

Defined in Crypto.Hash.Skein512

Show Skein512_384 
Instance details

Defined in Crypto.Hash.Skein512

Show Skein512_512 
Instance details

Defined in Crypto.Hash.Skein512

Show Tiger 
Instance details

Defined in Crypto.Hash.Tiger

Methods

showsPrec :: Int -> Tiger -> ShowS #

show :: Tiger -> String #

showList :: [Tiger] -> ShowS #

Show Whirlpool 
Instance details

Defined in Crypto.Hash.Whirlpool

Show CryptoError 
Instance details

Defined in Crypto.Error.Types

Show ConstructorInfo 
Instance details

Defined in Language.Haskell.TH.Datatype

Show DatatypeVariant 
Instance details

Defined in Language.Haskell.TH.Datatype

Show Extension 
Instance details

Defined in GHC.LanguageExtensions.Type

Show ForeignSrcLang 
Instance details

Defined in GHC.ForeignSrcLang.Type

Show Boxed 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> Boxed -> ShowS #

show :: Boxed -> String #

showList :: [Boxed] -> ShowS #

Show Tool 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> Tool -> ShowS #

show :: Tool -> String #

showList :: [Tool] -> ShowS #

Show SrcLoc 
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Show SrcSpan 
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Show SrcSpanInfo 
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Show Mode 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

showsPrec :: Int -> Mode -> ShowS #

show :: Mode -> String #

showList :: [Mode] -> ShowS #

Show Style 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

showsPrec :: Int -> Style -> ShowS #

show :: Style -> String #

showList :: [Style] -> ShowS #

Show RuleBndr 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Phases 
Instance details

Defined in Language.Haskell.TH.Syntax

Show RuleMatch 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Inline 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Pragma 
Instance details

Defined in Language.Haskell.TH.Syntax

Show DerivClause 
Instance details

Defined in Language.Haskell.TH.Syntax

Show DerivStrategy 
Instance details

Defined in Language.Haskell.TH.Syntax

Show TySynEqn 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Fixity 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Info 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Info -> ShowS #

show :: Info -> String #

showList :: [Info] -> ShowS #

Show Con 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Con -> ShowS #

show :: Con -> String #

showList :: [Con] -> ShowS #

Show TyVarBndr 
Instance details

Defined in Language.Haskell.TH.Syntax

Show DefName 
Instance details

Defined in Control.Lens.Internal.FieldTH

Show Pos 
Instance details

Defined in Text.Megaparsec.Pos

Methods

showsPrec :: Int -> Pos -> ShowS #

show :: Pos -> String #

showList :: [Pos] -> ShowS #

Show InvalidPosException 
Instance details

Defined in Text.Megaparsec.Pos

Show SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Show IsCmdStart 
Instance details

Defined in Options.Applicative.Types

Show Backtracking 
Instance details

Defined in Options.Applicative.Types

Show ParserPrefs 
Instance details

Defined in Options.Applicative.Types

Show OptName 
Instance details

Defined in Options.Applicative.Types

Show OptVisibility 
Instance details

Defined in Options.Applicative.Types

Show OptProperties 
Instance details

Defined in Options.Applicative.Types

Show CompletionResult 
Instance details

Defined in Options.Applicative.Types

Show ArgPolicy 
Instance details

Defined in Options.Applicative.Types

Show OptHelpInfo 
Instance details

Defined in Options.Applicative.Types

Show AltNodeType 
Instance details

Defined in Options.Applicative.Types

Show Doc 
Instance details

Defined in Text.PrettyPrint.HughesPJ

Methods

showsPrec :: Int -> Doc -> ShowS #

show :: Doc -> String #

showList :: [Doc] -> ShowS #

Show TextDetails 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Show ByteArray

Since: primitive-0.6.3.0

Instance details

Defined in Data.Primitive.ByteArray

Show UnicodeException 
Instance details

Defined in Data.Text.Encoding.Error

Show Mod2 
Instance details

Defined in Data.Semiring

Methods

showsPrec :: Int -> Mod2 -> ShowS #

show :: Mod2 -> String #

showList :: [Mod2] -> ShowS #

Show ResourceError 
Instance details

Defined in Test.Tasty.Core

Methods

showsPrec :: Int -> ResourceError -> ShowS #

show :: ResourceError -> String #

showList :: [ResourceError] -> ShowS #

Show FailureReason 
Instance details

Defined in Test.Tasty.Core

Show Outcome 
Instance details

Defined in Test.Tasty.Core

Show Result 
Instance details

Defined in Test.Tasty.Core

Show Progress 
Instance details

Defined in Test.Tasty.Core

Show DependencyType 
Instance details

Defined in Test.Tasty.Core

Show ForallVisFlag 
Instance details

Defined in Language.Haskell.TH.Ppr

Show ModName 
Instance details

Defined in Language.Haskell.TH.Syntax

Show PkgName 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Module 
Instance details

Defined in Language.Haskell.TH.Syntax

Show OccName 
Instance details

Defined in Language.Haskell.TH.Syntax

Show NameFlavour 
Instance details

Defined in Language.Haskell.TH.Syntax

Show NameSpace 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Loc 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Loc -> ShowS #

show :: Loc -> String #

showList :: [Loc] -> ShowS #

Show ModuleInfo 
Instance details

Defined in Language.Haskell.TH.Syntax

Show FixityDirection 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Lit 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Lit -> ShowS #

show :: Lit -> String #

showList :: [Lit] -> ShowS #

Show Bytes 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Bytes -> ShowS #

show :: Bytes -> String #

showList :: [Bytes] -> ShowS #

Show Body 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Body -> ShowS #

show :: Body -> String #

showList :: [Body] -> ShowS #

Show Guard 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Guard -> ShowS #

show :: Guard -> String #

showList :: [Guard] -> ShowS #

Show Stmt 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Stmt -> ShowS #

show :: Stmt -> String #

showList :: [Stmt] -> ShowS #

Show Range 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Range -> ShowS #

show :: Range -> String #

showList :: [Range] -> ShowS #

Show TypeFamilyHead 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Foreign 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Callconv 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Safety 
Instance details

Defined in Language.Haskell.TH.Syntax

Show AnnTarget 
Instance details

Defined in Language.Haskell.TH.Syntax

Show SourceUnpackedness 
Instance details

Defined in Language.Haskell.TH.Syntax

Show SourceStrictness 
Instance details

Defined in Language.Haskell.TH.Syntax

Show DecidedStrictness 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Bang 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Bang -> ShowS #

show :: Bang -> String #

showList :: [Bang] -> ShowS #

Show PatSynDir 
Instance details

Defined in Language.Haskell.TH.Syntax

Show PatSynArgs 
Instance details

Defined in Language.Haskell.TH.Syntax

Show FamilyResultSig 
Instance details

Defined in Language.Haskell.TH.Syntax

Show TyLit 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> TyLit -> ShowS #

show :: TyLit -> String #

showList :: [TyLit] -> ShowS #

Show Role 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Role -> ShowS #

show :: Role -> String #

showList :: [Role] -> ShowS #

Show AnnLookup 
Instance details

Defined in Language.Haskell.TH.Syntax

Show DatatypeInfo 
Instance details

Defined in Language.Haskell.TH.Datatype

Show ConstructorVariant 
Instance details

Defined in Language.Haskell.TH.Datatype

Show FieldStrictness 
Instance details

Defined in Language.Haskell.TH.Datatype

Show Unpackedness 
Instance details

Defined in Language.Haskell.TH.Datatype

Show Strictness 
Instance details

Defined in Language.Haskell.TH.Datatype

Show Specificity 
Instance details

Defined in Language.Haskell.TH.Datatype.TyVarBndr

Show DTypeArg 
Instance details

Defined in Language.Haskell.TH.Desugar.Core

Show DFunArgs 
Instance details

Defined in Language.Haskell.TH.Desugar.Core

Show DVisFunArg 
Instance details

Defined in Language.Haskell.TH.Desugar.Core

Show DExp 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

showsPrec :: Int -> DExp -> ShowS #

show :: DExp -> String #

showList :: [DExp] -> ShowS #

Show DPat 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

showsPrec :: Int -> DPat -> ShowS #

show :: DPat -> String #

showList :: [DPat] -> ShowS #

Show DType 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

showsPrec :: Int -> DType -> ShowS #

show :: DType -> String #

showList :: [DType] -> ShowS #

Show DTyVarBndr 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Show DMatch 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Show DClause 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Show DLetDec 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Show NewOrData 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Show DDec 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

showsPrec :: Int -> DDec -> ShowS #

show :: DDec -> String #

showList :: [DDec] -> ShowS #

Show DPatSynDir 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Show DTypeFamilyHead 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Show DFamilyResultSig 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Show DCon 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

showsPrec :: Int -> DCon -> ShowS #

show :: DCon -> String #

showList :: [DCon] -> ShowS #

Show DConFields 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Show DForeign 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Show DPragma 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Show DRuleBndr 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Show DTySynEqn 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Show DInfo 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

showsPrec :: Int -> DInfo -> ShowS #

show :: DInfo -> String #

showList :: [DInfo] -> ShowS #

Show DDerivClause 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Show DDerivStrategy 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Show ForallVisFlag 
Instance details

Defined in Language.Haskell.TH.Desugar.Util

Show FunArgs 
Instance details

Defined in Language.Haskell.TH.Desugar.Util

Show VisFunArg 
Instance details

Defined in Language.Haskell.TH.Desugar.Util

Show TypeArg 
Instance details

Defined in Language.Haskell.TH.Desugar.Util

Show ZonedTime 
Instance details

Defined in Data.Time.LocalTime.Internal.ZonedTime

Show LocalTime 
Instance details

Defined in Data.Time.LocalTime.Internal.LocalTime

Show DayOfWeek 
Instance details

Defined in Data.Time.Calendar.Week

Show Undefined 
Instance details

Defined in Universum.Debug

Show Bug 
Instance details

Defined in Universum.Exception

Methods

showsPrec :: Int -> Bug -> ShowS #

show :: Bug -> String #

showList :: [Bug] -> ShowS #

Show UnpackedUUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

showsPrec :: Int -> UnpackedUUID -> ShowS #

show :: UnpackedUUID -> String #

showList :: [UnpackedUUID] -> ShowS #

Show UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

showsPrec :: Int -> UUID -> ShowS #

show :: UUID -> String #

showList :: [UUID] -> ShowS #

Show Doc 
Instance details

Defined in Text.PrettyPrint.Leijen.Text

Methods

showsPrec :: Int -> Doc -> ShowS #

show :: Doc -> String #

showList :: [Doc] -> ShowS #

Show SimpleDoc 
Instance details

Defined in Text.PrettyPrint.Leijen.Text

Show MText 
Instance details

Defined in Michelson.Text

Methods

showsPrec :: Int -> MText -> ShowS #

show :: MText -> String #

showList :: [MText] -> ShowS #

Show AnnConvergeError 
Instance details

Defined in Michelson.Typed.Annotation

Methods

showsPrec :: Int -> AnnConvergeError -> ShowS #

show :: AnnConvergeError -> String #

showList :: [AnnConvergeError] -> ShowS #

Show MutezArithErrorType 
Instance details

Defined in Michelson.Typed.Arith

Methods

showsPrec :: Int -> MutezArithErrorType -> ShowS #

show :: MutezArithErrorType -> String #

showList :: [MutezArithErrorType] -> ShowS #

Show ShiftArithErrorType 
Instance details

Defined in Michelson.Typed.Arith

Methods

showsPrec :: Int -> ShiftArithErrorType -> ShowS #

show :: ShiftArithErrorType -> String #

showList :: [ShiftArithErrorType] -> ShowS #

Show ArmCoord 
Instance details

Defined in Michelson.Typed.Entrypoints

Methods

showsPrec :: Int -> ArmCoord -> ShowS #

show :: ArmCoord -> String #

showList :: [ArmCoord] -> ShowS #

Show EpAddress 
Instance details

Defined in Michelson.Typed.Entrypoints

Show ParamEpError 
Instance details

Defined in Michelson.Typed.Entrypoints

Methods

showsPrec :: Int -> ParamEpError -> ShowS #

show :: ParamEpError -> String #

showList :: [ParamEpError] -> ShowS #

Show ParseEpAddressError 
Instance details

Defined in Michelson.Typed.Entrypoints

Methods

showsPrec :: Int -> ParseEpAddressError -> ShowS #

show :: ParseEpAddressError -> String #

showList :: [ParseEpAddressError] -> ShowS #

Show DType 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Methods

showsPrec :: Int -> DType -> ShowS #

show :: DType -> String #

showList :: [DType] -> ShowS #

Show CommentType 
Instance details

Defined in Michelson.Typed.Instr

Methods

showsPrec :: Int -> CommentType -> ShowS #

show :: CommentType -> String #

showList :: [CommentType] -> ShowS #

Show BadTypeForScope 
Instance details

Defined in Michelson.Typed.Scope

Methods

showsPrec :: Int -> BadTypeForScope -> ShowS #

show :: BadTypeForScope -> String #

showList :: [BadTypeForScope] -> ShowS #

Show T 
Instance details

Defined in Michelson.Typed.T

Methods

showsPrec :: Int -> T -> ShowS #

show :: T -> String #

showList :: [T] -> ShowS #

Show SetDelegate 
Instance details

Defined in Michelson.Typed.Value

Methods

showsPrec :: Int -> SetDelegate -> ShowS #

show :: SetDelegate -> String #

showList :: [SetDelegate] -> ShowS #

Show EpName 
Instance details

Defined in Michelson.Untyped.Entrypoints

Show EpNameFromRefAnnError 
Instance details

Defined in Michelson.Untyped.Entrypoints

Methods

showsPrec :: Int -> EpNameFromRefAnnError -> ShowS #

show :: EpNameFromRefAnnError -> String #

showList :: [EpNameFromRefAnnError] -> ShowS #

Show OpSize 
Instance details

Defined in Michelson.Untyped.OpSize

Show Address 
Instance details

Defined in Tezos.Address

Show Bls12381Fr 
Instance details

Defined in Tezos.Crypto.BLS12381

Show Bls12381G1 
Instance details

Defined in Tezos.Crypto.BLS12381

Show Bls12381G2 
Instance details

Defined in Tezos.Crypto.BLS12381

Show ChainId 
Instance details

Defined in Tezos.Core

Show KeyHash 
Instance details

Defined in Tezos.Crypto

Show Mutez 
Instance details

Defined in Tezos.Core

Methods

showsPrec :: Int -> Mutez -> ShowS #

show :: Mutez -> String #

showList :: [Mutez] -> ShowS #

Show PublicKey 
Instance details

Defined in Tezos.Crypto

Show Signature 
Instance details

Defined in Tezos.Crypto

Show Timestamp 
Instance details

Defined in Tezos.Core

Show AnnotationSet 
Instance details

Defined in Michelson.Untyped.Annotation

Methods

showsPrec :: Int -> AnnotationSet -> ShowS #

show :: AnnotationSet -> String #

showList :: [AnnotationSet] -> ShowS #

Show VarAnns 
Instance details

Defined in Michelson.Untyped.Annotation

Methods

showsPrec :: Int -> VarAnns -> ShowS #

show :: VarAnns -> String #

showList :: [VarAnns] -> ShowS #

Show EntriesOrder 
Instance details

Defined in Michelson.Untyped.Contract

Methods

showsPrec :: Int -> EntriesOrder -> ShowS #

show :: EntriesOrder -> String #

showList :: [EntriesOrder] -> ShowS #

Show PrintComment 
Instance details

Defined in Michelson.Untyped.Ext

Methods

showsPrec :: Int -> PrintComment -> ShowS #

show :: PrintComment -> String #

showList :: [PrintComment] -> ShowS #

Show StackFn 
Instance details

Defined in Michelson.Untyped.Ext

Methods

showsPrec :: Int -> StackFn -> ShowS #

show :: StackFn -> String #

showList :: [StackFn] -> ShowS #

Show StackRef 
Instance details

Defined in Michelson.Untyped.Ext

Methods

showsPrec :: Int -> StackRef -> ShowS #

show :: StackRef -> String #

showList :: [StackRef] -> ShowS #

Show StackTypePattern 
Instance details

Defined in Michelson.Untyped.Ext

Methods

showsPrec :: Int -> StackTypePattern -> ShowS #

show :: StackTypePattern -> String #

showList :: [StackTypePattern] -> ShowS #

Show TyVar 
Instance details

Defined in Michelson.Untyped.Ext

Methods

showsPrec :: Int -> TyVar -> ShowS #

show :: TyVar -> String #

showList :: [TyVar] -> ShowS #

Show Var 
Instance details

Defined in Michelson.Untyped.Ext

Methods

showsPrec :: Int -> Var -> ShowS #

show :: Var -> String #

showList :: [Var] -> ShowS #

Show ExpandedOp 
Instance details

Defined in Michelson.Untyped.Instr

Methods

showsPrec :: Int -> ExpandedOp -> ShowS #

show :: ExpandedOp -> String #

showList :: [ExpandedOp] -> ShowS #

Show ParameterType 
Instance details

Defined in Michelson.Untyped.Type

Methods

showsPrec :: Int -> ParameterType -> ShowS #

show :: ParameterType -> String #

showList :: [ParameterType] -> ShowS #

Show T 
Instance details

Defined in Michelson.Untyped.Type

Methods

showsPrec :: Int -> T -> ShowS #

show :: T -> String #

showList :: [T] -> ShowS #

Show Ty 
Instance details

Defined in Michelson.Untyped.Type

Methods

showsPrec :: Int -> Ty -> ShowS #

show :: Ty -> String #

showList :: [Ty] -> ShowS #

Show InternalByteString 
Instance details

Defined in Michelson.Untyped.Value

Methods

showsPrec :: Int -> InternalByteString -> ShowS #

show :: InternalByteString -> String #

showList :: [InternalByteString] -> ShowS #

Show OperationHash 
Instance details

Defined in Tezos.Address

Methods

showsPrec :: Int -> OperationHash -> ShowS #

show :: OperationHash -> String #

showList :: [OperationHash] -> ShowS #

Show ContractHash 
Instance details

Defined in Tezos.Address

Methods

showsPrec :: Int -> ContractHash -> ShowS #

show :: ContractHash -> String #

showList :: [ContractHash] -> ShowS #

Show GlobalCounter 
Instance details

Defined in Tezos.Address

Methods

showsPrec :: Int -> GlobalCounter -> ShowS #

show :: GlobalCounter -> String #

showList :: [GlobalCounter] -> ShowS #

Show OriginationIndex 
Instance details

Defined in Tezos.Address

Methods

showsPrec :: Int -> OriginationIndex -> ShowS #

show :: OriginationIndex -> String #

showList :: [OriginationIndex] -> ShowS #

Show ParseAddressError 
Instance details

Defined in Tezos.Address

Methods

showsPrec :: Int -> ParseAddressError -> ShowS #

show :: ParseAddressError -> String #

showList :: [ParseAddressError] -> ShowS #

Show ParseAddressRawError 
Instance details

Defined in Tezos.Address

Methods

showsPrec :: Int -> ParseAddressRawError -> ShowS #

show :: ParseAddressRawError -> String #

showList :: [ParseAddressRawError] -> ShowS #

Show ParseContractAddressError 
Instance details

Defined in Tezos.Address

Methods

showsPrec :: Int -> ParseContractAddressError -> ShowS #

show :: ParseContractAddressError -> String #

showList :: [ParseContractAddressError] -> ShowS #

Show CryptoParseError 
Instance details

Defined in Tezos.Crypto.Util

Methods

showsPrec :: Int -> CryptoParseError -> ShowS #

show :: CryptoParseError -> String #

showList :: [CryptoParseError] -> ShowS #

Show ParseChainIdError 
Instance details

Defined in Tezos.Core

Methods

showsPrec :: Int -> ParseChainIdError -> ShowS #

show :: ParseChainIdError -> String #

showList :: [ParseChainIdError] -> ShowS #

Show KeyHashTag 
Instance details

Defined in Tezos.Crypto

Methods

showsPrec :: Int -> KeyHashTag -> ShowS #

show :: KeyHashTag -> String #

showList :: [KeyHashTag] -> ShowS #

Show SecretKey 
Instance details

Defined in Tezos.Crypto

Methods

showsPrec :: Int -> SecretKey -> ShowS #

show :: SecretKey -> String #

showList :: [SecretKey] -> ShowS #

Show B58CheckWithPrefixError 
Instance details

Defined in Tezos.Crypto.Util

Methods

showsPrec :: Int -> B58CheckWithPrefixError -> ShowS #

show :: B58CheckWithPrefixError -> String #

showList :: [B58CheckWithPrefixError] -> ShowS #

Show ParseSignatureRawError 
Instance details

Defined in Tezos.Crypto

Methods

showsPrec :: Int -> ParseSignatureRawError -> ShowS #

show :: ParseSignatureRawError -> String #

showList :: [ParseSignatureRawError] -> ShowS #

Show PublicKey 
Instance details

Defined in Tezos.Crypto.Ed25519

Methods

showsPrec :: Int -> PublicKey -> ShowS #

show :: PublicKey -> String #

showList :: [PublicKey] -> ShowS #

Show PublicKey 
Instance details

Defined in Tezos.Crypto.Secp256k1

Methods

showsPrec :: Int -> PublicKey -> ShowS #

show :: PublicKey -> String #

showList :: [PublicKey] -> ShowS #

Show PublicKey 
Instance details

Defined in Tezos.Crypto.P256

Methods

showsPrec :: Int -> PublicKey -> ShowS #

show :: PublicKey -> String #

showList :: [PublicKey] -> ShowS #

Show SecretKey 
Instance details

Defined in Tezos.Crypto.Ed25519

Methods

showsPrec :: Int -> SecretKey -> ShowS #

show :: SecretKey -> String #

showList :: [SecretKey] -> ShowS #

Show SecretKey 
Instance details

Defined in Tezos.Crypto.Secp256k1

Methods

showsPrec :: Int -> SecretKey -> ShowS #

show :: SecretKey -> String #

showList :: [SecretKey] -> ShowS #

Show SecretKey 
Instance details

Defined in Tezos.Crypto.P256

Methods

showsPrec :: Int -> SecretKey -> ShowS #

show :: SecretKey -> String #

showList :: [SecretKey] -> ShowS #

Show Signature 
Instance details

Defined in Tezos.Crypto.Ed25519

Methods

showsPrec :: Int -> Signature -> ShowS #

show :: Signature -> String #

showList :: [Signature] -> ShowS #

Show Signature 
Instance details

Defined in Tezos.Crypto.Secp256k1

Methods

showsPrec :: Int -> Signature -> ShowS #

show :: Signature -> String #

showList :: [Signature] -> ShowS #

Show Signature 
Instance details

Defined in Tezos.Crypto.P256

Methods

showsPrec :: Int -> Signature -> ShowS #

show :: Signature -> String #

showList :: [Signature] -> ShowS #

Show SomeDocItem 
Instance details

Defined in Michelson.Doc

Show DocItemPos 
Instance details

Defined in Michelson.Doc

Show DocSection 
Instance details

Defined in Michelson.Doc

Show InstrCallStack 
Instance details

Defined in Michelson.ErrorPos

Methods

showsPrec :: Int -> InstrCallStack -> ShowS #

show :: InstrCallStack -> String #

showList :: [InstrCallStack] -> ShowS #

Show DocGrouping 
Instance details

Defined in Michelson.Doc

Show DeserializationError 
Instance details

Defined in Tezos.Crypto.BLS12381

Methods

showsPrec :: Int -> DeserializationError -> ShowS #

show :: DeserializationError -> String #

showList :: [DeserializationError] -> ShowS #

Show DocItemId 
Instance details

Defined in Michelson.Doc

Show LetName 
Instance details

Defined in Michelson.ErrorPos

Methods

showsPrec :: Int -> LetName -> ShowS #

show :: LetName -> String #

showList :: [LetName] -> ShowS #

Show Pos 
Instance details

Defined in Michelson.ErrorPos

Methods

showsPrec :: Int -> Pos -> ShowS #

show :: Pos -> String #

showList :: [Pos] -> ShowS #

Show SrcPos 
Instance details

Defined in Michelson.ErrorPos

Methods

showsPrec :: Int -> SrcPos -> ShowS #

show :: SrcPos -> String #

showList :: [SrcPos] -> ShowS #

Show EpCallingStep Source # 
Instance details

Defined in Lorentz.Entrypoints.Core

Show CustomParserException 
Instance details

Defined in Michelson.Parser.Error

Methods

showsPrec :: Int -> CustomParserException -> ShowS #

show :: CustomParserException -> String #

showList :: [CustomParserException] -> ShowS #

Show ParserException 
Instance details

Defined in Michelson.Parser.Error

Methods

showsPrec :: Int -> ParserException -> ShowS #

show :: ParserException -> String #

showList :: [ParserException] -> ShowS #

Show StringLiteralParserException 
Instance details

Defined in Michelson.Parser.Error

Methods

showsPrec :: Int -> StringLiteralParserException -> ShowS #

show :: StringLiteralParserException -> String #

showList :: [StringLiteralParserException] -> ShowS #

Show ParsedOp 
Instance details

Defined in Michelson.Macro

Methods

showsPrec :: Int -> ParsedOp -> ShowS #

show :: ParsedOp -> String #

showList :: [ParsedOp] -> ShowS #

Show StackSize 
Instance details

Defined in Michelson.TypeCheck.Error

Methods

showsPrec :: Int -> StackSize -> ShowS #

show :: StackSize -> String #

showList :: [StackSize] -> ShowS #

Show TCError 
Instance details

Defined in Michelson.TypeCheck.Error

Methods

showsPrec :: Int -> TCError -> ShowS #

show :: TCError -> String #

showList :: [TCError] -> ShowS #

Show TCTypeError 
Instance details

Defined in Michelson.TypeCheck.Error

Methods

showsPrec :: Int -> TCTypeError -> ShowS #

show :: TCTypeError -> String #

showList :: [TCTypeError] -> ShowS #

Show TypeContext 
Instance details

Defined in Michelson.TypeCheck.Error

Methods

showsPrec :: Int -> TypeContext -> ShowS #

show :: TypeContext -> String #

showList :: [TypeContext] -> ShowS #

Show SomeParamType 
Instance details

Defined in Michelson.TypeCheck.TypeCheck

Methods

showsPrec :: Int -> SomeParamType -> ShowS #

show :: SomeParamType -> String #

showList :: [SomeParamType] -> ShowS #

Show SomeContract 
Instance details

Defined in Michelson.TypeCheck.Types

Methods

showsPrec :: Int -> SomeContract -> ShowS #

show :: SomeContract -> String #

showList :: [SomeContract] -> ShowS #

Show SomeContractAndStorage 
Instance details

Defined in Michelson.TypeCheck.Types

Methods

showsPrec :: Int -> SomeContractAndStorage -> ShowS #

show :: SomeContractAndStorage -> String #

showList :: [SomeContractAndStorage] -> ShowS #

Show SomeHST 
Instance details

Defined in Michelson.TypeCheck.Types

Methods

showsPrec :: Int -> SomeHST -> ShowS #

show :: SomeHST -> String #

showList :: [SomeHST] -> ShowS #

Show CadrStruct 
Instance details

Defined in Michelson.Macro

Methods

showsPrec :: Int -> CadrStruct -> ShowS #

show :: CadrStruct -> String #

showList :: [CadrStruct] -> ShowS #

Show LetMacro 
Instance details

Defined in Michelson.Macro

Methods

showsPrec :: Int -> LetMacro -> ShowS #

show :: LetMacro -> String #

showList :: [LetMacro] -> ShowS #

Show Macro 
Instance details

Defined in Michelson.Macro

Methods

showsPrec :: Int -> Macro -> ShowS #

show :: Macro -> String #

showList :: [Macro] -> ShowS #

Show PairStruct 
Instance details

Defined in Michelson.Macro

Methods

showsPrec :: Int -> PairStruct -> ShowS #

show :: PairStruct -> String #

showList :: [PairStruct] -> ShowS #

Show UnpairStruct 
Instance details

Defined in Michelson.Macro

Methods

showsPrec :: Int -> UnpairStruct -> ShowS #

show :: UnpairStruct -> String #

showList :: [UnpairStruct] -> ShowS #

Show Positive 
Instance details

Defined in Util.Positive

Methods

showsPrec :: Int -> Positive -> ShowS #

show :: Positive -> String #

showList :: [Positive] -> ShowS #

Show Never Source # 
Instance details

Defined in Lorentz.Value

Methods

showsPrec :: Int -> Never -> ShowS #

show :: Never -> String #

showList :: [Never] -> ShowS #

Show UnpackError 
Instance details

Defined in Util.Binary

Methods

showsPrec :: Int -> UnpackError -> ShowS #

show :: UnpackError -> String #

showList :: [UnpackError] -> ShowS #

Show FromExpressionError 
Instance details

Defined in Morley.Micheline.Class

Methods

showsPrec :: Int -> FromExpressionError -> ShowS #

show :: FromExpressionError -> String #

showList :: [FromExpressionError] -> ShowS #

Show Annotation 
Instance details

Defined in Morley.Micheline.Expression

Methods

showsPrec :: Int -> Annotation -> ShowS #

show :: Annotation -> String #

showList :: [Annotation] -> ShowS #

Show Expression 
Instance details

Defined in Morley.Micheline.Expression

Methods

showsPrec :: Int -> Expression -> ShowS #

show :: Expression -> String #

showList :: [Expression] -> ShowS #

Show MichelinePrimAp 
Instance details

Defined in Morley.Micheline.Expression

Methods

showsPrec :: Int -> MichelinePrimAp -> ShowS #

show :: MichelinePrimAp -> String #

showList :: [MichelinePrimAp] -> ShowS #

Show MichelinePrimitive 
Instance details

Defined in Morley.Micheline.Expression

Methods

showsPrec :: Int -> MichelinePrimitive -> ShowS #

show :: MichelinePrimitive -> String #

showList :: [MichelinePrimitive] -> ShowS #

Show TezosMutez 
Instance details

Defined in Morley.Micheline.Json

Methods

showsPrec :: Int -> TezosMutez -> ShowS #

show :: TezosMutez -> String #

showList :: [TezosMutez] -> ShowS #

Show HexJSONByteString 
Instance details

Defined in Util.ByteString

Methods

showsPrec :: Int -> HexJSONByteString -> ShowS #

show :: HexJSONByteString -> String #

showList :: [HexJSONByteString] -> ShowS #

Show ParamBuildingStep Source # 
Instance details

Defined in Lorentz.Entrypoints.Doc

Show ParamBuildingDesc Source # 
Instance details

Defined in Lorentz.Entrypoints.Doc

Show ParamBuilder Source # 
Instance details

Defined in Lorentz.Entrypoints.Doc

Show AnalyzerRes 
Instance details

Defined in Michelson.Analyzer

Methods

showsPrec :: Int -> AnalyzerRes -> ShowS #

show :: AnalyzerRes -> String #

showList :: [AnalyzerRes] -> ShowS #

Show InterpretError 
Instance details

Defined in Michelson.Interpret

Methods

showsPrec :: Int -> InterpretError -> ShowS #

show :: InterpretError -> String #

showList :: [InterpretError] -> ShowS #

Show InterpretResult 
Instance details

Defined in Michelson.Interpret

Methods

showsPrec :: Int -> InterpretResult -> ShowS #

show :: InterpretResult -> String #

showList :: [InterpretResult] -> ShowS #

Show InterpreterState 
Instance details

Defined in Michelson.Interpret

Methods

showsPrec :: Int -> InterpreterState -> ShowS #

show :: InterpreterState -> String #

showList :: [InterpreterState] -> ShowS #

Show MichelsonFailed 
Instance details

Defined in Michelson.Interpret

Methods

showsPrec :: Int -> MichelsonFailed -> ShowS #

show :: MichelsonFailed -> String #

showList :: [MichelsonFailed] -> ShowS #

Show MorleyLogs 
Instance details

Defined in Michelson.Interpret

Methods

showsPrec :: Int -> MorleyLogs -> ShowS #

show :: MorleyLogs -> String #

showList :: [MorleyLogs] -> ShowS #

Show RemainingSteps 
Instance details

Defined in Michelson.Interpret

Methods

showsPrec :: Int -> RemainingSteps -> ShowS #

show :: RemainingSteps -> String #

showList :: [RemainingSteps] -> ShowS #

Show VotingPowers 
Instance details

Defined in Michelson.Runtime.GState

Methods

showsPrec :: Int -> VotingPowers -> ShowS #

show :: VotingPowers -> String #

showList :: [VotingPowers] -> ShowS #

Show AddressState 
Instance details

Defined in Michelson.Runtime.GState

Methods

showsPrec :: Int -> AddressState -> ShowS #

show :: AddressState -> String #

showList :: [AddressState] -> ShowS #

Show ContractState 
Instance details

Defined in Michelson.Runtime.GState

Methods

showsPrec :: Int -> ContractState -> ShowS #

show :: ContractState -> String #

showList :: [ContractState] -> ShowS #

Show GState 
Instance details

Defined in Michelson.Runtime.GState

Methods

showsPrec :: Int -> GState -> ShowS #

show :: GState -> String #

showList :: [GState] -> ShowS #

Show GStateUpdate 
Instance details

Defined in Michelson.Runtime.GState

Methods

showsPrec :: Int -> GStateUpdate -> ShowS #

show :: GStateUpdate -> String #

showList :: [GStateUpdate] -> ShowS #

Show GStateUpdateError 
Instance details

Defined in Michelson.Runtime.GState

Methods

showsPrec :: Int -> GStateUpdateError -> ShowS #

show :: GStateUpdateError -> String #

showList :: [GStateUpdateError] -> ShowS #

Show GStateParseError 
Instance details

Defined in Michelson.Runtime.GState

Methods

showsPrec :: Int -> GStateParseError -> ShowS #

show :: GStateParseError -> String #

showList :: [GStateParseError] -> ShowS #

Show ExtConversionError Source # 
Instance details

Defined in Lorentz.Extensible

Show SomeError Source # 
Instance details

Defined in Lorentz.Errors

Show EntrypointLookupError Source # 
Instance details

Defined in Lorentz.UParam

Show BimapException 
Instance details

Defined in Data.Bimap

Methods

showsPrec :: Int -> BimapException -> ShowS #

show :: BimapException -> String #

showList :: [BimapException] -> ShowS #

Class () (Show a) 
Instance details

Defined in Data.Constraint

Methods

cls :: Show a :- () #

() :=> (Show Bool) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Show Bool #

() :=> (Show Char) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Show Char #

() :=> (Show Int) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Show Int #

() :=> (Show Natural) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Show Natural #

() :=> (Show Ordering) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Show Ordering #

() :=> (Show Word) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Show Word #

() :=> (Show ()) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Show () #

() :=> (Show (Dict a)) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Show (Dict a) #

() :=> (Show (a :- b)) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Show (a :- b) #

Show a => Show [a]

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> [a] -> ShowS #

show :: [a] -> String #

showList :: [[a]] -> ShowS #

Show a => Show (Maybe a)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> Maybe a -> ShowS #

show :: Maybe a -> String #

showList :: [Maybe a] -> ShowS #

Show a => Show (Ratio a)

Since: base-2.0.1

Instance details

Defined in GHC.Real

Methods

showsPrec :: Int -> Ratio a -> ShowS #

show :: Ratio a -> String #

showList :: [Ratio a] -> ShowS #

Show (Ptr a)

Since: base-2.1

Instance details

Defined in GHC.Ptr

Methods

showsPrec :: Int -> Ptr a -> ShowS #

show :: Ptr a -> String #

showList :: [Ptr a] -> ShowS #

Show (FunPtr a)

Since: base-2.1

Instance details

Defined in GHC.Ptr

Methods

showsPrec :: Int -> FunPtr a -> ShowS #

show :: FunPtr a -> String #

showList :: [FunPtr a] -> ShowS #

Show p => Show (Par1 p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> Par1 p -> ShowS #

show :: Par1 p -> String #

showList :: [Par1 p] -> ShowS #

Show a => Show (Only a) 
Instance details

Defined in Data.Tuple.Only

Methods

showsPrec :: Int -> Only a -> ShowS #

show :: Only a -> String #

showList :: [Only a] -> ShowS #

Show a => Show (IResult a) 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

showsPrec :: Int -> IResult a -> ShowS #

show :: IResult a -> String #

showList :: [IResult a] -> ShowS #

Show a => Show (Result a) 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

showsPrec :: Int -> Result a -> ShowS #

show :: Result a -> String #

showList :: [Result a] -> ShowS #

Show (ForeignPtr a)

Since: base-2.1

Instance details

Defined in GHC.ForeignPtr

Show a => Show (Complex a)

Since: base-2.1

Instance details

Defined in Data.Complex

Methods

showsPrec :: Int -> Complex a -> ShowS #

show :: Complex a -> String #

showList :: [Complex a] -> ShowS #

Show a => Show (Min a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

showsPrec :: Int -> Min a -> ShowS #

show :: Min a -> String #

showList :: [Min a] -> ShowS #

Show a => Show (Max a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

showsPrec :: Int -> Max a -> ShowS #

show :: Max a -> String #

showList :: [Max a] -> ShowS #

Show a => Show (First a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

showsPrec :: Int -> First a -> ShowS #

show :: First a -> String #

showList :: [First a] -> ShowS #

Show a => Show (Last a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

showsPrec :: Int -> Last a -> ShowS #

show :: Last a -> String #

showList :: [Last a] -> ShowS #

Show m => Show (WrappedMonoid m)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Show a => Show (Option a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

showsPrec :: Int -> Option a -> ShowS #

show :: Option a -> String #

showList :: [Option a] -> ShowS #

Show a => Show (ZipList a)

Since: base-4.7.0.0

Instance details

Defined in Control.Applicative

Methods

showsPrec :: Int -> ZipList a -> ShowS #

show :: ZipList a -> String #

showList :: [ZipList a] -> ShowS #

Show a => Show (Identity a)

This instance would be equivalent to the derived instances of the Identity newtype if the runIdentity field were removed

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Methods

showsPrec :: Int -> Identity a -> ShowS #

show :: Identity a -> String #

showList :: [Identity a] -> ShowS #

Show a => Show (First a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

showsPrec :: Int -> First a -> ShowS #

show :: First a -> String #

showList :: [First a] -> ShowS #

Show a => Show (Last a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

showsPrec :: Int -> Last a -> ShowS #

show :: Last a -> String #

showList :: [Last a] -> ShowS #

Show a => Show (Dual a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

showsPrec :: Int -> Dual a -> ShowS #

show :: Dual a -> String #

showList :: [Dual a] -> ShowS #

Show a => Show (Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

showsPrec :: Int -> Sum a -> ShowS #

show :: Sum a -> String #

showList :: [Sum a] -> ShowS #

Show a => Show (Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

showsPrec :: Int -> Product a -> ShowS #

show :: Product a -> String #

showList :: [Product a] -> ShowS #

Show a => Show (Down a)

This instance would be equivalent to the derived instances of the Down newtype if the getDown field were removed

Since: base-4.7.0.0

Instance details

Defined in Data.Ord

Methods

showsPrec :: Int -> Down a -> ShowS #

show :: Down a -> String #

showList :: [Down a] -> ShowS #

Show a => Show (NonEmpty a)

Since: base-4.11.0.0

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> NonEmpty a -> ShowS #

show :: NonEmpty a -> String #

showList :: [NonEmpty a] -> ShowS #

(PrimType ty, Show ty) => Show (UArray ty) 
Instance details

Defined in Basement.UArray.Base

Methods

showsPrec :: Int -> UArray ty -> ShowS #

show :: UArray ty -> String #

showList :: [UArray ty] -> ShowS #

(PrimType ty, Show ty) => Show (Block ty) 
Instance details

Defined in Basement.Block.Base

Methods

showsPrec :: Int -> Block ty -> ShowS #

show :: Block ty -> String #

showList :: [Block ty] -> ShowS #

Show a => Show (NonEmpty a) 
Instance details

Defined in Basement.NonEmpty

Methods

showsPrec :: Int -> NonEmpty a -> ShowS #

show :: NonEmpty a -> String #

showList :: [NonEmpty a] -> ShowS #

Show (Offset ty) 
Instance details

Defined in Basement.Types.OffsetSize

Methods

showsPrec :: Int -> Offset ty -> ShowS #

show :: Offset ty -> String #

showList :: [Offset ty] -> ShowS #

Show (CountOf ty) 
Instance details

Defined in Basement.Types.OffsetSize

Methods

showsPrec :: Int -> CountOf ty -> ShowS #

show :: CountOf ty -> String #

showList :: [CountOf ty] -> ShowS #

Show (Zn64 n) 
Instance details

Defined in Basement.Bounded

Methods

showsPrec :: Int -> Zn64 n -> ShowS #

show :: Zn64 n -> String #

showList :: [Zn64 n] -> ShowS #

Show (Zn n) 
Instance details

Defined in Basement.Bounded

Methods

showsPrec :: Int -> Zn n -> ShowS #

show :: Zn n -> String #

showList :: [Zn n] -> ShowS #

Show (Dict a) 
Instance details

Defined in Data.Constraint

Methods

showsPrec :: Int -> Dict a -> ShowS #

show :: Dict a -> String #

showList :: [Dict a] -> ShowS #

Show a => Show (IntMap a) 
Instance details

Defined in Data.IntMap.Internal

Methods

showsPrec :: Int -> IntMap a -> ShowS #

show :: IntMap a -> String #

showList :: [IntMap a] -> ShowS #

Show vertex => Show (SCC vertex)

Since: containers-0.5.9

Instance details

Defined in Data.Graph

Methods

showsPrec :: Int -> SCC vertex -> ShowS #

show :: SCC vertex -> String #

showList :: [SCC vertex] -> ShowS #

Show a => Show (Tree a) 
Instance details

Defined in Data.Tree

Methods

showsPrec :: Int -> Tree a -> ShowS #

show :: Tree a -> String #

showList :: [Tree a] -> ShowS #

Show a => Show (Seq a) 
Instance details

Defined in Data.Sequence.Internal

Methods

showsPrec :: Int -> Seq a -> ShowS #

show :: Seq a -> String #

showList :: [Seq a] -> ShowS #

Show a => Show (ViewL a) 
Instance details

Defined in Data.Sequence.Internal

Methods

showsPrec :: Int -> ViewL a -> ShowS #

show :: ViewL a -> String #

showList :: [ViewL a] -> ShowS #

Show a => Show (ViewR a) 
Instance details

Defined in Data.Sequence.Internal

Methods

showsPrec :: Int -> ViewR a -> ShowS #

show :: ViewR a -> String #

showList :: [ViewR a] -> ShowS #

Show a => Show (Set a) 
Instance details

Defined in Data.Set.Internal

Methods

showsPrec :: Int -> Set a -> ShowS #

show :: Set a -> String #

showList :: [Set a] -> ShowS #

Show (Blake2s bitlen) 
Instance details

Defined in Crypto.Hash.Blake2

Methods

showsPrec :: Int -> Blake2s bitlen -> ShowS #

show :: Blake2s bitlen -> String #

showList :: [Blake2s bitlen] -> ShowS #

Show (Blake2b bitlen) 
Instance details

Defined in Crypto.Hash.Blake2

Methods

showsPrec :: Int -> Blake2b bitlen -> ShowS #

show :: Blake2b bitlen -> String #

showList :: [Blake2b bitlen] -> ShowS #

Show (Blake2sp bitlen) 
Instance details

Defined in Crypto.Hash.Blake2

Methods

showsPrec :: Int -> Blake2sp bitlen -> ShowS #

show :: Blake2sp bitlen -> String #

showList :: [Blake2sp bitlen] -> ShowS #

Show (Blake2bp bitlen) 
Instance details

Defined in Crypto.Hash.Blake2

Methods

showsPrec :: Int -> Blake2bp bitlen -> ShowS #

show :: Blake2bp bitlen -> String #

showList :: [Blake2bp bitlen] -> ShowS #

Show (SHAKE128 bitlen) 
Instance details

Defined in Crypto.Hash.SHAKE

Methods

showsPrec :: Int -> SHAKE128 bitlen -> ShowS #

show :: SHAKE128 bitlen -> String #

showList :: [SHAKE128 bitlen] -> ShowS #

Show (SHAKE256 bitlen) 
Instance details

Defined in Crypto.Hash.SHAKE

Methods

showsPrec :: Int -> SHAKE256 bitlen -> ShowS #

show :: SHAKE256 bitlen -> String #

showList :: [SHAKE256 bitlen] -> ShowS #

Show (Digest a) 
Instance details

Defined in Crypto.Hash.Types

Methods

showsPrec :: Int -> Digest a -> ShowS #

show :: Digest a -> String #

showList :: [Digest a] -> ShowS #

Show a => Show (CryptoFailable a) 
Instance details

Defined in Crypto.Error.Types

Show1 f => Show (Fix f) 
Instance details

Defined in Data.Fix

Methods

showsPrec :: Int -> Fix f -> ShowS #

show :: Fix f -> String #

showList :: [Fix f] -> ShowS #

(Functor f, Show1 f) => Show (Mu f) 
Instance details

Defined in Data.Fix

Methods

showsPrec :: Int -> Mu f -> ShowS #

show :: Mu f -> String #

showList :: [Mu f] -> ShowS #

(Functor f, Show1 f) => Show (Nu f) 
Instance details

Defined in Data.Fix

Methods

showsPrec :: Int -> Nu f -> ShowS #

show :: Nu f -> String #

showList :: [Nu f] -> ShowS #

Show a => Show (DList a) 
Instance details

Defined in Data.DList

Methods

showsPrec :: Int -> DList a -> ShowS #

show :: DList a -> String #

showList :: [DList a] -> ShowS #

Show a => Show (ExitCase a) 
Instance details

Defined in Control.Monad.Catch

Methods

showsPrec :: Int -> ExitCase a -> ShowS #

show :: ExitCase a -> String #

showList :: [ExitCase a] -> ShowS #

Show (Finite n) 
Instance details

Defined in Data.Finite.Internal

Methods

showsPrec :: Int -> Finite n -> ShowS #

show :: Finite n -> String #

showList :: [Finite n] -> ShowS #

Show a => Show (Hashed a) 
Instance details

Defined in Data.Hashable.Class

Methods

showsPrec :: Int -> Hashed a -> ShowS #

show :: Hashed a -> String #

showList :: [Hashed a] -> ShowS #

Show l => Show (PragmasAndModuleName l) 
Instance details

Defined in Language.Haskell.Exts.Parser

Show l => Show (PragmasAndModuleHead l) 
Instance details

Defined in Language.Haskell.Exts.Parser

Show l => Show (ModuleHeadAndImports l) 
Instance details

Defined in Language.Haskell.Exts.Parser

Show a => Show (NonGreedy a) 
Instance details

Defined in Language.Haskell.Exts.Parser

Show a => Show (ListOf a) 
Instance details

Defined in Language.Haskell.Exts.Parser

Methods

showsPrec :: Int -> ListOf a -> ShowS #

show :: ListOf a -> String #

showList :: [ListOf a] -> ShowS #

Show l => Show (ModuleName l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show (SpecialCon l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show (QName l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> QName l -> ShowS #

show :: QName l -> String #

showList :: [QName l] -> ShowS #

Show l => Show (Name l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> Name l -> ShowS #

show :: Name l -> String #

showList :: [Name l] -> ShowS #

Show l => Show (IPName l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> IPName l -> ShowS #

show :: IPName l -> String #

showList :: [IPName l] -> ShowS #

Show l => Show (QOp l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> QOp l -> ShowS #

show :: QOp l -> String #

showList :: [QOp l] -> ShowS #

Show l => Show (Op l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> Op l -> ShowS #

show :: Op l -> String #

showList :: [Op l] -> ShowS #

Show l => Show (CName l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> CName l -> ShowS #

show :: CName l -> String #

showList :: [CName l] -> ShowS #

Show l => Show (Module l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> Module l -> ShowS #

show :: Module l -> String #

showList :: [Module l] -> ShowS #

Show l => Show (ModuleHead l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show (ExportSpecList l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show (ExportSpec l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show (EWildcard l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show (Namespace l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show (ImportDecl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show (ImportSpecList l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show (ImportSpec l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show (Assoc l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> Assoc l -> ShowS #

show :: Assoc l -> String #

showList :: [Assoc l] -> ShowS #

Show l => Show (Decl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> Decl l -> ShowS #

show :: Decl l -> String #

showList :: [Decl l] -> ShowS #

Show l => Show (PatternSynDirection l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show (TypeEqn l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> TypeEqn l -> ShowS #

show :: TypeEqn l -> String #

showList :: [TypeEqn l] -> ShowS #

Show l => Show (Annotation l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show (BooleanFormula l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show (Role l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> Role l -> ShowS #

show :: Role l -> String #

showList :: [Role l] -> ShowS #

Show l => Show (DataOrNew l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show (InjectivityInfo l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show (ResultSig l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show (DeclHead l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> DeclHead l -> ShowS #

show :: DeclHead l -> String #

showList :: [DeclHead l] -> ShowS #

Show l => Show (InstRule l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> InstRule l -> ShowS #

show :: InstRule l -> String #

showList :: [InstRule l] -> ShowS #

Show l => Show (InstHead l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> InstHead l -> ShowS #

show :: InstHead l -> String #

showList :: [InstHead l] -> ShowS #

Show l => Show (Deriving l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> Deriving l -> ShowS #

show :: Deriving l -> String #

showList :: [Deriving l] -> ShowS #

Show l => Show (DerivStrategy l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show (Binds l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> Binds l -> ShowS #

show :: Binds l -> String #

showList :: [Binds l] -> ShowS #

Show l => Show (IPBind l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> IPBind l -> ShowS #

show :: IPBind l -> String #

showList :: [IPBind l] -> ShowS #

Show l => Show (Match l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> Match l -> ShowS #

show :: Match l -> String #

showList :: [Match l] -> ShowS #

Show l => Show (QualConDecl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show (ConDecl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> ConDecl l -> ShowS #

show :: ConDecl l -> String #

showList :: [ConDecl l] -> ShowS #

Show l => Show (FieldDecl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show (GadtDecl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> GadtDecl l -> ShowS #

show :: GadtDecl l -> String #

showList :: [GadtDecl l] -> ShowS #

Show l => Show (ClassDecl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show (InstDecl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> InstDecl l -> ShowS #

show :: InstDecl l -> String #

showList :: [InstDecl l] -> ShowS #

Show l => Show (BangType l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> BangType l -> ShowS #

show :: BangType l -> String #

showList :: [BangType l] -> ShowS #

Show l => Show (Unpackedness l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show (Rhs l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> Rhs l -> ShowS #

show :: Rhs l -> String #

showList :: [Rhs l] -> ShowS #

Show l => Show (GuardedRhs l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show (Type l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> Type l -> ShowS #

show :: Type l -> String #

showList :: [Type l] -> ShowS #

Show l => Show (MaybePromotedName l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show (Promoted l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> Promoted l -> ShowS #

show :: Promoted l -> String #

showList :: [Promoted l] -> ShowS #

Show l => Show (TyVarBind l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show (FunDep l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> FunDep l -> ShowS #

show :: FunDep l -> String #

showList :: [FunDep l] -> ShowS #

Show l => Show (Context l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> Context l -> ShowS #

show :: Context l -> String #

showList :: [Context l] -> ShowS #

Show l => Show (Asst l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> Asst l -> ShowS #

show :: Asst l -> String #

showList :: [Asst l] -> ShowS #

Show l => Show (Literal l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> Literal l -> ShowS #

show :: Literal l -> String #

showList :: [Literal l] -> ShowS #

Show l => Show (Sign l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> Sign l -> ShowS #

show :: Sign l -> String #

showList :: [Sign l] -> ShowS #

Show l => Show (Exp l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> Exp l -> ShowS #

show :: Exp l -> String #

showList :: [Exp l] -> ShowS #

Show l => Show (XName l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> XName l -> ShowS #

show :: XName l -> String #

showList :: [XName l] -> ShowS #

Show l => Show (XAttr l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> XAttr l -> ShowS #

show :: XAttr l -> String #

showList :: [XAttr l] -> ShowS #

Show l => Show (Bracket l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> Bracket l -> ShowS #

show :: Bracket l -> String #

showList :: [Bracket l] -> ShowS #

Show l => Show (Splice l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> Splice l -> ShowS #

show :: Splice l -> String #

showList :: [Splice l] -> ShowS #

Show l => Show (Safety l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> Safety l -> ShowS #

show :: Safety l -> String #

showList :: [Safety l] -> ShowS #

Show l => Show (CallConv l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> CallConv l -> ShowS #

show :: CallConv l -> String #

showList :: [CallConv l] -> ShowS #

Show l => Show (ModulePragma l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show (Overlap l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> Overlap l -> ShowS #

show :: Overlap l -> String #

showList :: [Overlap l] -> ShowS #

Show l => Show (Activation l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show (Rule l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> Rule l -> ShowS #

show :: Rule l -> String #

showList :: [Rule l] -> ShowS #

Show l => Show (RuleVar l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> RuleVar l -> ShowS #

show :: RuleVar l -> String #

showList :: [RuleVar l] -> ShowS #

Show l => Show (WarningText l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show (Pat l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> Pat l -> ShowS #

show :: Pat l -> String #

showList :: [Pat l] -> ShowS #

Show l => Show (PXAttr l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> PXAttr l -> ShowS #

show :: PXAttr l -> String #

showList :: [PXAttr l] -> ShowS #

Show l => Show (RPatOp l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> RPatOp l -> ShowS #

show :: RPatOp l -> String #

showList :: [RPatOp l] -> ShowS #

Show l => Show (RPat l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> RPat l -> ShowS #

show :: RPat l -> String #

showList :: [RPat l] -> ShowS #

Show l => Show (PatField l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> PatField l -> ShowS #

show :: PatField l -> String #

showList :: [PatField l] -> ShowS #

Show l => Show (Stmt l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> Stmt l -> ShowS #

show :: Stmt l -> String #

showList :: [Stmt l] -> ShowS #

Show l => Show (QualStmt l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> QualStmt l -> ShowS #

show :: QualStmt l -> String #

showList :: [QualStmt l] -> ShowS #

Show l => Show (FieldUpdate l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show (Alt l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

showsPrec :: Int -> Alt l -> ShowS #

show :: Alt l -> String #

showList :: [Alt l] -> ShowS #

Show a => Show (Loc a) 
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Methods

showsPrec :: Int -> Loc a -> ShowS #

show :: Loc a -> String #

showList :: [Loc a] -> ShowS #

(Show a, Prim a) => Show (Vector a) 
Instance details

Defined in Data.Vector.Primitive

Methods

showsPrec :: Int -> Vector a -> ShowS #

show :: Vector a -> String #

showList :: [Vector a] -> ShowS #

(Show a, Storable a) => Show (Vector a) 
Instance details

Defined in Data.Vector.Storable

Methods

showsPrec :: Int -> Vector a -> ShowS #

show :: Vector a -> String #

showList :: [Vector a] -> ShowS #

Show a => Show (HashSet a) 
Instance details

Defined in Data.HashSet.Internal

Methods

showsPrec :: Int -> HashSet a -> ShowS #

show :: HashSet a -> String #

showList :: [HashSet a] -> ShowS #

Show a => Show (Vector a) 
Instance details

Defined in Data.Vector

Methods

showsPrec :: Int -> Vector a -> ShowS #

show :: Vector a -> String #

showList :: [Vector a] -> ShowS #

Show t => Show (ErrorItem t) 
Instance details

Defined in Text.Megaparsec.Error

Show e => Show (ErrorFancy e) 
Instance details

Defined in Text.Megaparsec.Error

Show s => Show (PosState s) 
Instance details

Defined in Text.Megaparsec.State

Methods

showsPrec :: Int -> PosState s -> ShowS #

show :: PosState s -> String #

showList :: [PosState s] -> ShowS #

KnownNat m => Show (Mod m) 
Instance details

Defined in Data.Mod

Methods

showsPrec :: Int -> Mod m -> ShowS #

show :: Mod m -> String #

showList :: [Mod m] -> ShowS #

Show (Option a) 
Instance details

Defined in Options.Applicative.Types

Methods

showsPrec :: Int -> Option a -> ShowS #

show :: Option a -> String #

showList :: [Option a] -> ShowS #

Show h => Show (ParserFailure h) 
Instance details

Defined in Options.Applicative.Types

Show a => Show (ParserResult a) 
Instance details

Defined in Options.Applicative.Types

Show a => Show (OptTree a) 
Instance details

Defined in Options.Applicative.Types

Methods

showsPrec :: Int -> OptTree a -> ShowS #

show :: OptTree a -> String #

showList :: [OptTree a] -> ShowS #

Show (Doc a) 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

showsPrec :: Int -> Doc a -> ShowS #

show :: Doc a -> String #

showList :: [Doc a] -> ShowS #

Show a => Show (AnnotDetails a) 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Show a => Show (Span a) 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

showsPrec :: Int -> Span a -> ShowS #

show :: Span a -> String #

showList :: [Span a] -> ShowS #

(Show a, Prim a) => Show (PrimArray a)

Since: primitive-0.6.4.0

Instance details

Defined in Data.Primitive.PrimArray

Show a => Show (SmallArray a) 
Instance details

Defined in Data.Primitive.SmallArray

Show a => Show (Array a) 
Instance details

Defined in Data.Primitive.Array

Methods

showsPrec :: Int -> Array a -> ShowS #

show :: Array a -> String #

showList :: [Array a] -> ShowS #

Show a => Show (Add a) 
Instance details

Defined in Data.Semiring

Methods

showsPrec :: Int -> Add a -> ShowS #

show :: Add a -> String #

showList :: [Add a] -> ShowS #

Show a => Show (Mul a) 
Instance details

Defined in Data.Semiring

Methods

showsPrec :: Int -> Mul a -> ShowS #

show :: Mul a -> String #

showList :: [Mul a] -> ShowS #

Show a => Show (WrappedNum a) 
Instance details

Defined in Data.Semiring

Show (IntSetOf a) 
Instance details

Defined in Data.Semiring

Methods

showsPrec :: Int -> IntSetOf a -> ShowS #

show :: IntSetOf a -> String #

showList :: [IntSetOf a] -> ShowS #

Show a => Show (Maybe a) 
Instance details

Defined in Data.Strict.Maybe

Methods

showsPrec :: Int -> Maybe a -> ShowS #

show :: Maybe a -> String #

showList :: [Maybe a] -> ShowS #

Show a => Show (Identity a) 
Instance details

Defined in Data.Vinyl.Functor

Methods

showsPrec :: Int -> Identity a -> ShowS #

show :: Identity a -> String #

showList :: [Identity a] -> ShowS #

Show a => Show (Thunk a) 
Instance details

Defined in Data.Vinyl.Functor

Methods

showsPrec :: Int -> Thunk a -> ShowS #

show :: Thunk a -> String #

showList :: [Thunk a] -> ShowS #

(Show t, KnownSymbol s) => Show (ElField '(s, t)) 
Instance details

Defined in Data.Vinyl.Functor

Methods

showsPrec :: Int -> ElField '(s, t) -> ShowS #

show :: ElField '(s, t) -> String #

showList :: [ElField '(s, t)] -> ShowS #

Show (Label name) 
Instance details

Defined in Util.Label

Methods

showsPrec :: Int -> Label name -> ShowS #

show :: Label name -> String #

showList :: [Label name] -> ShowS #

Show (Notes t) 
Instance details

Defined in Michelson.Typed.Annotation

Methods

showsPrec :: Int -> Notes t -> ShowS #

show :: Notes t -> String #

showList :: [Notes t] -> ShowS #

Show (ParamNotes t) 
Instance details

Defined in Michelson.Typed.Entrypoints

Methods

showsPrec :: Int -> ParamNotes t -> ShowS #

show :: ParamNotes t -> String #

showList :: [ParamNotes t] -> ShowS #

Show (SomeEntrypointCallT arg) 
Instance details

Defined in Michelson.Typed.Entrypoints

Methods

showsPrec :: Int -> SomeEntrypointCallT arg -> ShowS #

show :: SomeEntrypointCallT arg -> String #

showList :: [SomeEntrypointCallT arg] -> ShowS #

Show (ContractRef arg) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Methods

showsPrec :: Int -> ContractRef arg -> ShowS #

show :: ContractRef arg -> String #

showList :: [ContractRef arg] -> ShowS #

Show (ExtInstr s) 
Instance details

Defined in Michelson.Typed.Instr

Methods

showsPrec :: Int -> ExtInstr s -> ShowS #

show :: ExtInstr s -> String #

showList :: [ExtInstr s] -> ShowS #

Show (PrintComment st) 
Instance details

Defined in Michelson.Typed.Instr

Methods

showsPrec :: Int -> PrintComment st -> ShowS #

show :: PrintComment st -> String #

showList :: [PrintComment st] -> ShowS #

Show (StackRef st) 
Instance details

Defined in Michelson.Typed.Instr

Methods

showsPrec :: Int -> StackRef st -> ShowS #

show :: StackRef st -> String #

showList :: [StackRef st] -> ShowS #

Show (TestAssert s) 
Instance details

Defined in Michelson.Typed.Instr

Methods

showsPrec :: Int -> TestAssert s -> ShowS #

show :: TestAssert s -> String #

showList :: [TestAssert s] -> ShowS #

Show (CtorEffectsApp x) 
Instance details

Defined in Michelson.Typed.Util

Methods

showsPrec :: Int -> CtorEffectsApp x -> ShowS #

show :: CtorEffectsApp x -> String #

showList :: [CtorEffectsApp x] -> ShowS #

Show (DfsSettings x) 
Instance details

Defined in Michelson.Typed.Util

Methods

showsPrec :: Int -> DfsSettings x -> ShowS #

show :: DfsSettings x -> String #

showList :: [DfsSettings x] -> ShowS #

Show (Operation' instr) 
Instance details

Defined in Michelson.Typed.Value

Methods

showsPrec :: Int -> Operation' instr -> ShowS #

show :: Operation' instr -> String #

showList :: [Operation' instr] -> ShowS #

Show (SomeValue' instr) 
Instance details

Defined in Michelson.Typed.Value

Methods

showsPrec :: Int -> SomeValue' instr -> ShowS #

show :: SomeValue' instr -> String #

showList :: [SomeValue' instr] -> ShowS #

Show op => Show (Contract' op) 
Instance details

Defined in Michelson.Untyped.Contract

Methods

showsPrec :: Int -> Contract' op -> ShowS #

show :: Contract' op -> String #

showList :: [Contract' op] -> ShowS #

Show op => Show (ContractBlock op) 
Instance details

Defined in Michelson.Untyped.Contract

Methods

showsPrec :: Int -> ContractBlock op -> ShowS #

show :: ContractBlock op -> String #

showList :: [ContractBlock op] -> ShowS #

Show op => Show (ExtInstrAbstract op) 
Instance details

Defined in Michelson.Untyped.Ext

Methods

showsPrec :: Int -> ExtInstrAbstract op -> ShowS #

show :: ExtInstrAbstract op -> String #

showList :: [ExtInstrAbstract op] -> ShowS #

Show op => Show (TestAssert op) 
Instance details

Defined in Michelson.Untyped.Ext

Methods

showsPrec :: Int -> TestAssert op -> ShowS #

show :: TestAssert op -> String #

showList :: [TestAssert op] -> ShowS #

RenderDoc (InstrAbstract op) => Show (InstrAbstract op) 
Instance details

Defined in Michelson.Untyped.Instr

Methods

showsPrec :: Int -> InstrAbstract op -> ShowS #

show :: InstrAbstract op -> String #

showList :: [InstrAbstract op] -> ShowS #

Show op => Show (Elt op) 
Instance details

Defined in Michelson.Untyped.Value

Methods

showsPrec :: Int -> Elt op -> ShowS #

show :: Elt op -> String #

showList :: [Elt op] -> ShowS #

Show op => Show (Value' op) 
Instance details

Defined in Michelson.Untyped.Value

Methods

showsPrec :: Int -> Value' op -> ShowS #

show :: Value' op -> String #

showList :: [Value' op] -> ShowS #

Show (SingNat n) 
Instance details

Defined in Util.Peano

Methods

showsPrec :: Int -> SingNat n -> ShowS #

show :: SingNat n -> String #

showList :: [SingNat n] -> ShowS #

KnownNat p => Show (Prime p) 
Instance details

Defined in Data.Field.Galois.Prime

Methods

showsPrec :: Int -> Prime p -> ShowS #

show :: Prime p -> String #

showList :: [Prime p] -> ShowS #

Show (Binary p) 
Instance details

Defined in Data.Field.Galois.Binary

Methods

showsPrec :: Int -> Binary p -> ShowS #

show :: Binary p -> String #

showList :: [Binary p] -> ShowS #

Show (EpCallingDesc info) Source # 
Instance details

Defined in Lorentz.Entrypoints.Core

Methods

showsPrec :: Int -> EpCallingDesc info -> ShowS #

show :: EpCallingDesc info -> String #

showList :: [EpCallingDesc info] -> ShowS #

Show (HST ts) 
Instance details

Defined in Michelson.TypeCheck.Types

Methods

showsPrec :: Int -> HST ts -> ShowS #

show :: HST ts -> String #

showList :: [HST ts] -> ShowS #

Show (ExtInstr inp) => Show (SomeInstr inp) 
Instance details

Defined in Michelson.TypeCheck.Types

Methods

showsPrec :: Int -> SomeInstr inp -> ShowS #

show :: SomeInstr inp -> String #

showList :: [SomeInstr inp] -> ShowS #

Show (ExtInstr inp) => Show (SomeInstrOut inp) 
Instance details

Defined in Michelson.TypeCheck.Types

Methods

showsPrec :: Int -> SomeInstrOut inp -> ShowS #

show :: SomeInstrOut inp -> String #

showList :: [SomeInstrOut inp] -> ShowS #

Show (TSignature a) Source # 
Instance details

Defined in Lorentz.Bytes

Show (Packed a) Source # 
Instance details

Defined in Lorentz.Bytes

Methods

showsPrec :: Int -> Packed a -> ShowS #

show :: Packed a -> String #

showList :: [Packed a] -> ShowS #

Show a => Show (StringEncode a) 
Instance details

Defined in Morley.Micheline.Json

Methods

showsPrec :: Int -> StringEncode a -> ShowS #

show :: StringEncode a -> String #

showList :: [StringEncode a] -> ShowS #

Show (StkEl t) 
Instance details

Defined in Michelson.Interpret

Methods

showsPrec :: Int -> StkEl t -> ShowS #

show :: StkEl t -> String #

showList :: [StkEl t] -> ShowS #

Show (CustomErrorRep tag) => Show (CustomError tag) Source # 
Instance details

Defined in Lorentz.Errors

Methods

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

show :: CustomError tag -> String #

showList :: [CustomError tag] -> ShowS #

Show (ConstrainedSome Show) Source # 
Instance details

Defined in Lorentz.UParam

Show (UParam entries) Source # 
Instance details

Defined in Lorentz.UParam

Methods

showsPrec :: Int -> UParam entries -> ShowS #

show :: UParam entries -> String #

showList :: [UParam entries] -> ShowS #

(Show a) :=> (Show (Complex a)) 
Instance details

Defined in Data.Constraint

Methods

ins :: Show a :- Show (Complex a) #

(Show a) :=> (Show [a]) 
Instance details

Defined in Data.Constraint

Methods

ins :: Show a :- Show [a] #

(Show a) :=> (Show (Maybe a)) 
Instance details

Defined in Data.Constraint

Methods

ins :: Show a :- Show (Maybe a) #

(Show a) :=> (Show (Identity a)) 
Instance details

Defined in Data.Constraint

Methods

ins :: Show a :- Show (Identity a) #

(Show a) :=> (Show (Const a b)) 
Instance details

Defined in Data.Constraint

Methods

ins :: Show a :- Show (Const a b) #

Show (CustomErrorRep tag) => Show (() -> CustomError tag) Source # 
Instance details

Defined in Lorentz.Errors

Methods

showsPrec :: Int -> (() -> CustomError tag) -> ShowS #

show :: (() -> CustomError tag) -> String #

showList :: [() -> CustomError tag] -> ShowS #

(Show a, Show b) => Show (Either a b)

Since: base-3.0

Instance details

Defined in Data.Either

Methods

showsPrec :: Int -> Either a b -> ShowS #

show :: Either a b -> String #

showList :: [Either a b] -> ShowS #

Show (V1 p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> V1 p -> ShowS #

show :: V1 p -> String #

showList :: [V1 p] -> ShowS #

Show (U1 p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> U1 p -> ShowS #

show :: U1 p -> String #

showList :: [U1 p] -> ShowS #

Show (TypeRep a) 
Instance details

Defined in Data.Typeable.Internal

Methods

showsPrec :: Int -> TypeRep a -> ShowS #

show :: TypeRep a -> String #

showList :: [TypeRep a] -> ShowS #

(Show a, Show b) => Show (a, b)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b) -> ShowS #

show :: (a, b) -> String #

showList :: [(a, b)] -> ShowS #

Show (ST s a)

Since: base-2.1

Instance details

Defined in GHC.ST

Methods

showsPrec :: Int -> ST s a -> ShowS #

show :: ST s a -> String #

showList :: [ST s a] -> ShowS #

(Show k, Show v) => Show (HashMap k v) 
Instance details

Defined in Data.HashMap.Internal

Methods

showsPrec :: Int -> HashMap k v -> ShowS #

show :: HashMap k v -> String #

showList :: [HashMap k v] -> ShowS #

(Show k, Show a) => Show (Map k a) 
Instance details

Defined in Data.Map.Internal

Methods

showsPrec :: Int -> Map k a -> ShowS #

show :: Map k a -> String #

showList :: [Map k a] -> ShowS #

(Show i, Show r) => Show (IResult i r) 
Instance details

Defined in Data.Attoparsec.Internal.Types

Methods

showsPrec :: Int -> IResult i r -> ShowS #

show :: IResult i r -> String #

showList :: [IResult i r] -> ShowS #

(Show a, Show b) => Show (Arg a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

showsPrec :: Int -> Arg a b -> ShowS #

show :: Arg a b -> String #

showList :: [Arg a b] -> ShowS #

Show (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

showsPrec :: Int -> Proxy s -> ShowS #

show :: Proxy s -> String #

showList :: [Proxy s] -> ShowS #

(Show a, Show b) => Show (Bimap a b) 
Instance details

Defined in Data.Bimap

Methods

showsPrec :: Int -> Bimap a b -> ShowS #

show :: Bimap a b -> String #

showList :: [Bimap a b] -> ShowS #

Show (a :- b) 
Instance details

Defined in Data.Constraint

Methods

showsPrec :: Int -> (a :- b) -> ShowS #

show :: (a :- b) -> String #

showList :: [a :- b] -> ShowS #

(Show1 m, Show a) => Show (MaybeT m a) 
Instance details

Defined in Control.Monad.Trans.Maybe

Methods

showsPrec :: Int -> MaybeT m a -> ShowS #

show :: MaybeT m a -> String #

showList :: [MaybeT m a] -> ShowS #

(Show1 f, Show a) => Show (Cofree f a) 
Instance details

Defined in Control.Comonad.Cofree

Methods

showsPrec :: Int -> Cofree f a -> ShowS #

show :: Cofree f a -> String #

showList :: [Cofree f a] -> ShowS #

(Show1 f, Show a) => Show (Free f a) 
Instance details

Defined in Control.Monad.Free

Methods

showsPrec :: Int -> Free f a -> ShowS #

show :: Free f a -> String #

showList :: [Free f a] -> ShowS #

Show (f a) => Show (Yoneda f a) 
Instance details

Defined in Data.Functor.Yoneda

Methods

showsPrec :: Int -> Yoneda f a -> ShowS #

show :: Yoneda f a -> String #

showList :: [Yoneda f a] -> ShowS #

(Show s, Show (Token s), Show e) => Show (ParseErrorBundle s e) 
Instance details

Defined in Text.Megaparsec.Error

(Show (ParseError s e), Show s) => Show (State s e) 
Instance details

Defined in Text.Megaparsec.State

Methods

showsPrec :: Int -> State s e -> ShowS #

show :: State s e -> String #

showList :: [State s e] -> ShowS #

(Show (Token s), Show e) => Show (ParseError s e) 
Instance details

Defined in Text.Megaparsec.Error

Methods

showsPrec :: Int -> ParseError s e -> ShowS #

show :: ParseError s e -> String #

showList :: [ParseError s e] -> ShowS #

(Show a, Vector v a) => Show (Poly v a) 
Instance details

Defined in Data.Poly.Internal.Dense

Methods

showsPrec :: Int -> Poly v a -> ShowS #

show :: Poly v a -> String #

showList :: [Poly v a] -> ShowS #

Show v => Show (IntMapOf k v) 
Instance details

Defined in Data.Semiring

Methods

showsPrec :: Int -> IntMapOf k v -> ShowS #

show :: IntMapOf k v -> String #

showList :: [IntMapOf k v] -> ShowS #

ShowSing (Maybe a) => Show (SFirst z) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Methods

showsPrec :: Int -> SFirst z -> ShowS #

show :: SFirst z -> String #

showList :: [SFirst z] -> ShowS #

ShowSing (Maybe a) => Show (SLast z) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Methods

showsPrec :: Int -> SLast z -> ShowS #

show :: SLast z -> String #

showList :: [SLast z] -> ShowS #

(Show a, Show b) => Show (Pair a b) 
Instance details

Defined in Data.Strict.Tuple

Methods

showsPrec :: Int -> Pair a b -> ShowS #

show :: Pair a b -> String #

showList :: [Pair a b] -> ShowS #

(Show a, Show b) => Show (These a b) 
Instance details

Defined in Data.Strict.These

Methods

showsPrec :: Int -> These a b -> ShowS #

show :: These a b -> String #

showList :: [These a b] -> ShowS #

(Show a, Show b) => Show (Either a b) 
Instance details

Defined in Data.Strict.Either

Methods

showsPrec :: Int -> Either a b -> ShowS #

show :: Either a b -> String #

showList :: [Either a b] -> ShowS #

(Show a, Show b) => Show (These a b) 
Instance details

Defined in Data.These

Methods

showsPrec :: Int -> These a b -> ShowS #

show :: These a b -> String #

showList :: [These a b] -> ShowS #

(Show n, Show m) => Show (ArithError n m) 
Instance details

Defined in Michelson.Typed.Arith

Methods

showsPrec :: Int -> ArithError n m -> ShowS #

show :: ArithError n m -> String #

showList :: [ArithError n m] -> ShowS #

Show (EntrypointCallT param arg) 
Instance details

Defined in Michelson.Typed.Entrypoints

Methods

showsPrec :: Int -> EntrypointCallT param arg -> ShowS #

show :: EntrypointCallT param arg -> String #

showList :: [EntrypointCallT param arg] -> ShowS #

Show (EpLiftSequence arg param) 
Instance details

Defined in Michelson.Typed.Entrypoints

Methods

showsPrec :: Int -> EpLiftSequence arg param -> ShowS #

show :: EpLiftSequence arg param -> String #

showList :: [EpLiftSequence arg param] -> ShowS #

(Show k, Show v) => Show (BigMap k v) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Methods

showsPrec :: Int -> BigMap k v -> ShowS #

show :: BigMap k v -> String #

showList :: [BigMap k v] -> ShowS #

Show (Contract cp st) 
Instance details

Defined in Michelson.Typed.Instr

Methods

showsPrec :: Int -> Contract cp st -> ShowS #

show :: Contract cp st -> String #

showList :: [Contract cp st] -> ShowS #

Show (Instr inp out) 
Instance details

Defined in Michelson.Typed.Instr

Methods

showsPrec :: Int -> Instr inp out -> ShowS #

show :: Instr inp out -> String #

showList :: [Instr inp out] -> ShowS #

Show (SomeConstrainedValue' instr c) 
Instance details

Defined in Michelson.Typed.Value

Methods

showsPrec :: Int -> SomeConstrainedValue' instr c -> ShowS #

show :: SomeConstrainedValue' instr c -> String #

showList :: [SomeConstrainedValue' instr c] -> ShowS #

Show (TransferTokens instr p) 
Instance details

Defined in Michelson.Typed.Value

Methods

showsPrec :: Int -> TransferTokens instr p -> ShowS #

show :: TransferTokens instr p -> String #

showList :: [TransferTokens instr p] -> ShowS #

Show (Value' instr t) 
Instance details

Defined in Michelson.Typed.Value

Methods

showsPrec :: Int -> Value' instr t -> ShowS #

show :: Value' instr t -> String #

showList :: [Value' instr t] -> ShowS #

KnownAnnTag tag => Show (Annotation tag) 
Instance details

Defined in Michelson.Untyped.Annotation

Methods

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

show :: Annotation tag -> String #

showList :: [Annotation tag] -> ShowS #

Show k => Show (RootsOfUnity n k) 
Instance details

Defined in Data.Field.Galois.Unity

Methods

showsPrec :: Int -> RootsOfUnity n k -> ShowS #

show :: RootsOfUnity n k -> String #

showList :: [RootsOfUnity n k] -> ShowS #

Show k => Show (Extension p k) 
Instance details

Defined in Data.Field.Galois.Extension

Methods

showsPrec :: Int -> Extension p k -> ShowS #

show :: Extension p k -> String #

showList :: [Extension p k] -> ShowS #

(forall (a :: k). Show (f a)) => Show (Some1 f) 
Instance details

Defined in Util.Type

Methods

showsPrec :: Int -> Some1 f -> ShowS #

show :: Some1 f -> String #

showList :: [Some1 f] -> ShowS #

Show (inp :-> out) Source # 
Instance details

Defined in Lorentz.Base

Methods

showsPrec :: Int -> (inp :-> out) -> ShowS #

show :: (inp :-> out) -> String #

showList :: [inp :-> out] -> ShowS #

Show (TAddress p) Source # 
Instance details

Defined in Lorentz.Address

Methods

showsPrec :: Int -> TAddress p -> ShowS #

show :: TAddress p -> String #

showList :: [TAddress p] -> ShowS #

Show (Hash alg a) Source # 
Instance details

Defined in Lorentz.Bytes

Methods

showsPrec :: Int -> Hash alg a -> ShowS #

show :: Hash alg a -> String #

showList :: [Hash alg a] -> ShowS #

Show (Extensible x) Source # 
Instance details

Defined in Lorentz.Extensible

Show a => Show (Void_ a b) Source # 
Instance details

Defined in Lorentz.Macro

Methods

showsPrec :: Int -> Void_ a b -> ShowS #

show :: Void_ a b -> String #

showList :: [Void_ a b] -> ShowS #

Show a => Show (View a r) Source # 
Instance details

Defined in Lorentz.Macro

Methods

showsPrec :: Int -> View a r -> ShowS #

show :: View a r -> String #

showList :: [View a r] -> ShowS #

(Integral a, Show a) :=> (Show (Ratio a)) 
Instance details

Defined in Data.Constraint

Methods

ins :: (Integral a, Show a) :- Show (Ratio a) #

(Show a, Show b) :=> (Show (a, b)) 
Instance details

Defined in Data.Constraint

Methods

ins :: (Show a, Show b) :- Show (a, b) #

(Show a, Show b) :=> (Show (Either a b)) 
Instance details

Defined in Data.Constraint

Methods

ins :: (Show a, Show b) :- Show (Either a b) #

Show (f p) => Show (Rec1 f p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> Rec1 f p -> ShowS #

show :: Rec1 f p -> String #

showList :: [Rec1 f p] -> ShowS #

Show (URec Char p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> URec Char p -> ShowS #

show :: URec Char p -> String #

showList :: [URec Char p] -> ShowS #

Show (URec Double p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> URec Double p -> ShowS #

show :: URec Double p -> String #

showList :: [URec Double p] -> ShowS #

Show (URec Float p) 
Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> URec Float p -> ShowS #

show :: URec Float p -> String #

showList :: [URec Float p] -> ShowS #

Show (URec Int p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> URec Int p -> ShowS #

show :: URec Int p -> String #

showList :: [URec Int p] -> ShowS #

Show (URec Word p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> URec Word p -> ShowS #

show :: URec Word p -> String #

showList :: [URec Word p] -> ShowS #

(Show a, Show b, Show c) => Show (a, b, c)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c) -> ShowS #

show :: (a, b, c) -> String #

showList :: [(a, b, c)] -> ShowS #

Show a => Show (Const a b)

This instance would be equivalent to the derived instances of the Const newtype if the getConst field were removed

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Const

Methods

showsPrec :: Int -> Const a b -> ShowS #

show :: Const a b -> String #

showList :: [Const a b] -> ShowS #

Show (f a) => Show (Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

showsPrec :: Int -> Ap f a -> ShowS #

show :: Ap f a -> String #

showList :: [Ap f a] -> ShowS #

Show (f a) => Show (Alt f a)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

showsPrec :: Int -> Alt f a -> ShowS #

show :: Alt f a -> String #

showList :: [Alt f a] -> ShowS #

Show (a :~: b)

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Equality

Methods

showsPrec :: Int -> (a :~: b) -> ShowS #

show :: (a :~: b) -> String #

showList :: [a :~: b] -> ShowS #

Show (p a a) => Show (Join p a) 
Instance details

Defined in Data.Bifunctor.Join

Methods

showsPrec :: Int -> Join p a -> ShowS #

show :: Join p a -> String #

showList :: [Join p a] -> ShowS #

Show (p (Fix p a) a) => Show (Fix p a) 
Instance details

Defined in Data.Bifunctor.Fix

Methods

showsPrec :: Int -> Fix p a -> ShowS #

show :: Fix p a -> String #

showList :: [Fix p a] -> ShowS #

(Show1 f, Show a) => Show (IdentityT f a) 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

showsPrec :: Int -> IdentityT f a -> ShowS #

show :: IdentityT f a -> String #

showList :: [IdentityT f a] -> ShowS #

(Show e, Show1 m, Show a) => Show (ExceptT e m a) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

showsPrec :: Int -> ExceptT e m a -> ShowS #

show :: ExceptT e m a -> String #

showList :: [ExceptT e m a] -> ShowS #

(Show a, Show (f b)) => Show (FreeF f a b) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

showsPrec :: Int -> FreeF f a b -> ShowS #

show :: FreeF f a b -> String #

showList :: [FreeF f a b] -> ShowS #

(Show1 f, Show1 m, Show a) => Show (FreeT f m a) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

showsPrec :: Int -> FreeT f m a -> ShowS #

show :: FreeT f m a -> String #

showList :: [FreeT f m a] -> ShowS #

(Show a, Show (f b)) => Show (CofreeF f a b) 
Instance details

Defined in Control.Comonad.Trans.Cofree

Methods

showsPrec :: Int -> CofreeF f a b -> ShowS #

show :: CofreeF f a b -> String #

showList :: [CofreeF f a b] -> ShowS #

Show (w (CofreeF f a (CofreeT f w a))) => Show (CofreeT f w a) 
Instance details

Defined in Control.Comonad.Trans.Cofree

Methods

showsPrec :: Int -> CofreeT f w a -> ShowS #

show :: CofreeT f w a -> String #

showList :: [CofreeT f w a] -> ShowS #

(Show e, Show1 m, Show a) => Show (ErrorT e m a) 
Instance details

Defined in Control.Monad.Trans.Error

Methods

showsPrec :: Int -> ErrorT e m a -> ShowS #

show :: ErrorT e m a -> String #

showList :: [ErrorT e m a] -> ShowS #

Show b => Show (Tagged s b) 
Instance details

Defined in Data.Tagged

Methods

showsPrec :: Int -> Tagged s b -> ShowS #

show :: Tagged s b -> String #

showList :: [Tagged s b] -> ShowS #

(Show a, KnownNat n, Vector v (Vector n Word, a)) => Show (MultiPoly v n a) 
Instance details

Defined in Data.Poly.Internal.Multi

Methods

showsPrec :: Int -> MultiPoly v n a -> ShowS #

show :: MultiPoly v n a -> String #

showList :: [MultiPoly v n a] -> ShowS #

(ShowSing a, ShowSing b) => Show (SArg z) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Methods

showsPrec :: Int -> SArg z -> ShowS #

show :: SArg z -> String #

showList :: [SArg z] -> ShowS #

Show (SProxy z) 
Instance details

Defined in Data.Singletons.Prelude.Proxy

Methods

showsPrec :: Int -> SProxy z -> ShowS #

show :: SProxy z -> String #

showList :: [SProxy z] -> ShowS #

(Show1 f, Show1 g, Show a) => Show (These1 f g a) 
Instance details

Defined in Data.Functor.These

Methods

showsPrec :: Int -> These1 f g a -> ShowS #

show :: These1 f g a -> String #

showList :: [These1 f g a] -> ShowS #

(RPureConstrained (IndexableField rs) rs, RecApplicative rs, Show (Rec f rs)) => Show (ARec f rs) 
Instance details

Defined in Data.Vinyl.ARec

Methods

showsPrec :: Int -> ARec f rs -> ShowS #

show :: ARec f rs -> String #

showList :: [ARec f rs] -> ShowS #

(RMap rs, ReifyConstraint Show f rs, RecordToList rs) => Show (Rec f rs)

Records may be shown insofar as their points may be shown. reifyConstraint is used to great effect here.

Instance details

Defined in Data.Vinyl.Core

Methods

showsPrec :: Int -> Rec f rs -> ShowS #

show :: Rec f rs -> String #

showList :: [Rec f rs] -> ShowS #

Show a => Show (Const a b) 
Instance details

Defined in Data.Vinyl.Functor

Methods

showsPrec :: Int -> Const a b -> ShowS #

show :: Const a b -> String #

showList :: [Const a b] -> ShowS #

Show (CreateContract instr cp st) 
Instance details

Defined in Michelson.Typed.Value

Methods

showsPrec :: Int -> CreateContract instr cp st -> ShowS #

show :: CreateContract instr cp st -> String #

showList :: [CreateContract instr cp st] -> ShowS #

Show c => Show (K1 i c p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> K1 i c p -> ShowS #

show :: K1 i c p -> String #

showList :: [K1 i c p] -> ShowS #

(Show (f p), Show (g p)) => Show ((f :+: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> (f :+: g) p -> ShowS #

show :: (f :+: g) p -> String #

showList :: [(f :+: g) p] -> ShowS #

(Show (f p), Show (g p)) => Show ((f :*: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> (f :*: g) p -> ShowS #

show :: (f :*: g) p -> String #

showList :: [(f :*: g) p] -> ShowS #

(Show a, Show b, Show c, Show d) => Show (a, b, c, d)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d) -> ShowS #

show :: (a, b, c, d) -> String #

showList :: [(a, b, c, d)] -> ShowS #

(Show1 f, Show1 g, Show a) => Show (Product f g a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

showsPrec :: Int -> Product f g a -> ShowS #

show :: Product f g a -> String #

showList :: [Product f g a] -> ShowS #

(Show1 f, Show1 g, Show a) => Show (Sum f g a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

showsPrec :: Int -> Sum f g a -> ShowS #

show :: Sum f g a -> String #

showList :: [Sum f g a] -> ShowS #

Show (a :~~: b)

Since: base-4.10.0.0

Instance details

Defined in Data.Type.Equality

Methods

showsPrec :: Int -> (a :~~: b) -> ShowS #

show :: (a :~~: b) -> String #

showList :: [a :~~: b] -> ShowS #

(forall (o' :: k). Show (instr i o')) => Show (RemFail instr i o) 
Instance details

Defined in Michelson.Typed.Value

Methods

showsPrec :: Int -> RemFail instr i o -> ShowS #

show :: RemFail instr i o -> String #

showList :: [RemFail instr i o] -> ShowS #

Show (f p) => Show (M1 i c f p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> M1 i c f p -> ShowS #

show :: M1 i c f p -> String #

showList :: [M1 i c f p] -> ShowS #

Show (f (g p)) => Show ((f :.: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> (f :.: g) p -> ShowS #

show :: (f :.: g) p -> String #

showList :: [(f :.: g) p] -> ShowS #

(Show a, Show b, Show c, Show d, Show e) => Show (a, b, c, d, e)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e) -> ShowS #

show :: (a, b, c, d, e) -> String #

showList :: [(a, b, c, d, e)] -> ShowS #

(Show1 f, Show1 g, Show a) => Show (Compose f g a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

showsPrec :: Int -> Compose f g a -> ShowS #

show :: Compose f g a -> String #

showList :: [Compose f g a] -> ShowS #

Show (p a b) => Show (WrappedBifunctor p a b) 
Instance details

Defined in Data.Bifunctor.Wrapped

Show (g b) => Show (Joker g a b) 
Instance details

Defined in Data.Bifunctor.Joker

Methods

showsPrec :: Int -> Joker g a b -> ShowS #

show :: Joker g a b -> String #

showList :: [Joker g a b] -> ShowS #

Show (p b a) => Show (Flip p a b) 
Instance details

Defined in Data.Bifunctor.Flip

Methods

showsPrec :: Int -> Flip p a b -> ShowS #

show :: Flip p a b -> String #

showList :: [Flip p a b] -> ShowS #

Show (f a) => Show (Clown f a b) 
Instance details

Defined in Data.Bifunctor.Clown

Methods

showsPrec :: Int -> Clown f a b -> ShowS #

show :: Clown f a b -> String #

showList :: [Clown f a b] -> ShowS #

Show (f (g a)) => Show (Compose f g a) 
Instance details

Defined in Data.Vinyl.Functor

Methods

showsPrec :: Int -> Compose f g a -> ShowS #

show :: Compose f g a -> String #

showList :: [Compose f g a] -> ShowS #

(Show a, Show b, Show c, Show d, Show e, Show f) => Show (a, b, c, d, e, f)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f) -> ShowS #

show :: (a, b, c, d, e, f) -> String #

showList :: [(a, b, c, d, e, f)] -> ShowS #

(Show (p a b), Show (q a b)) => Show (Sum p q a b) 
Instance details

Defined in Data.Bifunctor.Sum

Methods

showsPrec :: Int -> Sum p q a b -> ShowS #

show :: Sum p q a b -> String #

showList :: [Sum p q a b] -> ShowS #

(Show (f a b), Show (g a b)) => Show (Product f g a b) 
Instance details

Defined in Data.Bifunctor.Product

Methods

showsPrec :: Int -> Product f g a b -> ShowS #

show :: Product f g a b -> String #

showList :: [Product f g a b] -> ShowS #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g) => Show (a, b, c, d, e, f, g)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g) -> ShowS #

show :: (a, b, c, d, e, f, g) -> String #

showList :: [(a, b, c, d, e, f, g)] -> ShowS #

Show (f (p a b)) => Show (Tannen f p a b) 
Instance details

Defined in Data.Bifunctor.Tannen

Methods

showsPrec :: Int -> Tannen f p a b -> ShowS #

show :: Tannen f p a b -> String #

showList :: [Tannen f p a b] -> ShowS #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h) => Show (a, b, c, d, e, f, g, h)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h) -> ShowS #

show :: (a, b, c, d, e, f, g, h) -> String #

showList :: [(a, b, c, d, e, f, g, h)] -> ShowS #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i) => Show (a, b, c, d, e, f, g, h, i)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i) -> ShowS #

show :: (a, b, c, d, e, f, g, h, i) -> String #

showList :: [(a, b, c, d, e, f, g, h, i)] -> ShowS #

Show (p (f a) (g b)) => Show (Biff p f g a b) 
Instance details

Defined in Data.Bifunctor.Biff

Methods

showsPrec :: Int -> Biff p f g a b -> ShowS #

show :: Biff p f g a b -> String #

showList :: [Biff p f g a b] -> ShowS #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j) => Show (a, b, c, d, e, f, g, h, i, j)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j) -> ShowS #

show :: (a, b, c, d, e, f, g, h, i, j) -> String #

showList :: [(a, b, c, d, e, f, g, h, i, j)] -> ShowS #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k) => Show (a, b, c, d, e, f, g, h, i, j, k)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k) -> ShowS #

show :: (a, b, c, d, e, f, g, h, i, j, k) -> String #

showList :: [(a, b, c, d, e, f, g, h, i, j, k)] -> ShowS #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l) => Show (a, b, c, d, e, f, g, h, i, j, k, l)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k, l) -> ShowS #

show :: (a, b, c, d, e, f, g, h, i, j, k, l) -> String #

showList :: [(a, b, c, d, e, f, g, h, i, j, k, l)] -> ShowS #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m) => Show (a, b, c, d, e, f, g, h, i, j, k, l, m)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> ShowS #

show :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> String #

showList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m)] -> ShowS #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m, Show n) => Show (a, b, c, d, e, f, g, h, i, j, k, l, m, n)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> ShowS #

show :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> String #

showList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] -> ShowS #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m, Show n, Show o) => Show (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> ShowS #

show :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> String #

showList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)] -> ShowS #

class Default a where #

A class for types with a default value.

Minimal complete definition

Nothing

Methods

def :: a #

The default value for this type.

Instances

Instances details
Default Double 
Instance details

Defined in Data.Default.Class

Methods

def :: Double #

Default Float 
Instance details

Defined in Data.Default.Class

Methods

def :: Float #

Default Int 
Instance details

Defined in Data.Default.Class

Methods

def :: Int #

Default Int8 
Instance details

Defined in Data.Default.Class

Methods

def :: Int8 #

Default Int16 
Instance details

Defined in Data.Default.Class

Methods

def :: Int16 #

Default Int32 
Instance details

Defined in Data.Default.Class

Methods

def :: Int32 #

Default Int64 
Instance details

Defined in Data.Default.Class

Methods

def :: Int64 #

Default Integer 
Instance details

Defined in Data.Default.Class

Methods

def :: Integer #

Default Ordering 
Instance details

Defined in Data.Default.Class

Methods

def :: Ordering #

Default Word 
Instance details

Defined in Data.Default.Class

Methods

def :: Word #

Default Word8 
Instance details

Defined in Data.Default.Class

Methods

def :: Word8 #

Default Word16 
Instance details

Defined in Data.Default.Class

Methods

def :: Word16 #

Default Word32 
Instance details

Defined in Data.Default.Class

Methods

def :: Word32 #

Default Word64 
Instance details

Defined in Data.Default.Class

Methods

def :: Word64 #

Default () 
Instance details

Defined in Data.Default.Class

Methods

def :: () #

Default All 
Instance details

Defined in Data.Default.Class

Methods

def :: All #

Default Any 
Instance details

Defined in Data.Default.Class

Methods

def :: Any #

Default CShort 
Instance details

Defined in Data.Default.Class

Methods

def :: CShort #

Default CUShort 
Instance details

Defined in Data.Default.Class

Methods

def :: CUShort #

Default CInt 
Instance details

Defined in Data.Default.Class

Methods

def :: CInt #

Default CUInt 
Instance details

Defined in Data.Default.Class

Methods

def :: CUInt #

Default CLong 
Instance details

Defined in Data.Default.Class

Methods

def :: CLong #

Default CULong 
Instance details

Defined in Data.Default.Class

Methods

def :: CULong #

Default CLLong 
Instance details

Defined in Data.Default.Class

Methods

def :: CLLong #

Default CULLong 
Instance details

Defined in Data.Default.Class

Methods

def :: CULLong #

Default CFloat 
Instance details

Defined in Data.Default.Class

Methods

def :: CFloat #

Default CDouble 
Instance details

Defined in Data.Default.Class

Methods

def :: CDouble #

Default CPtrdiff 
Instance details

Defined in Data.Default.Class

Methods

def :: CPtrdiff #

Default CSize 
Instance details

Defined in Data.Default.Class

Methods

def :: CSize #

Default CSigAtomic 
Instance details

Defined in Data.Default.Class

Methods

def :: CSigAtomic #

Default CClock 
Instance details

Defined in Data.Default.Class

Methods

def :: CClock #

Default CTime 
Instance details

Defined in Data.Default.Class

Methods

def :: CTime #

Default CUSeconds 
Instance details

Defined in Data.Default.Class

Methods

def :: CUSeconds #

Default CSUSeconds 
Instance details

Defined in Data.Default.Class

Methods

def :: CSUSeconds #

Default CIntPtr 
Instance details

Defined in Data.Default.Class

Methods

def :: CIntPtr #

Default CUIntPtr 
Instance details

Defined in Data.Default.Class

Methods

def :: CUIntPtr #

Default CIntMax 
Instance details

Defined in Data.Default.Class

Methods

def :: CIntMax #

Default CUIntMax 
Instance details

Defined in Data.Default.Class

Methods

def :: CUIntMax #

Default EntriesOrder 
Instance details

Defined in Michelson.Untyped.Contract

Methods

def :: EntriesOrder #

Default InstrCallStack 
Instance details

Defined in Michelson.ErrorPos

Methods

def :: InstrCallStack #

Default Pos 
Instance details

Defined in Michelson.ErrorPos

Methods

def :: Pos #

Default SrcPos 
Instance details

Defined in Michelson.ErrorPos

Methods

def :: SrcPos #

Default OptimizerConf 
Instance details

Defined in Michelson.Optimizer

Methods

def :: OptimizerConf #

Default TypeCheckOptions 
Instance details

Defined in Michelson.TypeCheck.TypeCheck

Methods

def :: TypeCheckOptions #

Default MorleyLogs 
Instance details

Defined in Michelson.Interpret

Methods

def :: MorleyLogs #

Default [a] 
Instance details

Defined in Data.Default.Class

Methods

def :: [a] #

Default (Maybe a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Maybe a #

Integral a => Default (Ratio a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Ratio a #

Default a => Default (IO a) 
Instance details

Defined in Data.Default.Class

Methods

def :: IO a #

(Default a, RealFloat a) => Default (Complex a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Complex a #

Default (First a) 
Instance details

Defined in Data.Default.Class

Methods

def :: First a #

Default (Last a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Last a #

Default a => Default (Dual a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Dual a #

Default (Endo a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Endo a #

Num a => Default (Sum a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Sum a #

Num a => Default (Product a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Product a #

Default (DfsSettings x) 
Instance details

Defined in Michelson.Typed.Util

Methods

def :: DfsSettings x #

Default r => Default (e -> r) 
Instance details

Defined in Data.Default.Class

Methods

def :: e -> r #

(Default a, Default b) => Default (a, b) 
Instance details

Defined in Data.Default.Class

Methods

def :: (a, b) #

Default (BigMap k v) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Methods

def :: BigMap k v #

Default (Annotation tag) 
Instance details

Defined in Michelson.Untyped.Annotation

Methods

def :: Annotation tag #

(Default a, Default b, Default c) => Default (a, b, c) 
Instance details

Defined in Data.Default.Class

Methods

def :: (a, b, c) #

(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) #

(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) #

(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) #

(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) #

data Label (name :: Symbol) where #

Constructors

Label :: forall (name :: Symbol). KnownSymbol name => Label name 

Instances

Instances details
(KnownSymbol name, s ~ name) => IsLabel s (Label name) 
Instance details

Defined in Util.Label

Methods

fromLabel :: Label name #

Eq (Label name) 
Instance details

Defined in Util.Label

Methods

(==) :: Label name -> Label name -> Bool #

(/=) :: Label name -> Label name -> Bool #

Show (Label name) 
Instance details

Defined in Util.Label

Methods

showsPrec :: Int -> Label name -> ShowS #

show :: Label name -> String #

showList :: [Label name] -> ShowS #

Buildable (Label name) 
Instance details

Defined in Util.Label

Methods

build :: Label name -> Builder #

newtype PrintAsValue a Source #

Provides Buildable instance that prints Lorentz value via Michelson's Value.

Result won't be very pretty, but this avoids requiring Show or Buildable instances.

Constructors

PrintAsValue a 

Instances

Instances details
NicePrintedValue a => Buildable (PrintAsValue a) Source # 
Instance details

Defined in Lorentz.Value

Methods

build :: PrintAsValue a -> Builder #

Re-exports