morley-0.5.0: Developer tools for the Michelson Language

Safe HaskellNone
LanguageHaskell2010

Lorentz.Value

Contents

Description

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

Synopsis

Documentation

class IsoValue a where Source #

Isomorphism between Michelson values and plain Haskell types.

Default implementation of this typeclass converts ADTs to Michelson "pair"s and "or"s.

Minimal complete definition

Nothing

Associated Types

type ToT a :: T Source #

Type function that converts a regular Haskell type into a T type.

Methods

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

Converts a Haskell structure into Value representation.

toVal :: (Generic a, GIsoValue (Rep a), ToT a ~ GValueType (Rep a)) => a -> Value (ToT a) Source #

Converts a Haskell structure into Value representation.

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

Converts a Value into Haskell type.

fromVal :: (Generic a, GIsoValue (Rep a), ToT a ~ GValueType (Rep a)) => Value (ToT a) -> a Source #

Converts a Value into Haskell type.

Instances
IsoValue Bool Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Bool :: T Source #

IsoValue Integer Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Integer :: T Source #

IsoValue Natural Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Natural :: T Source #

IsoValue () Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT () :: T Source #

Methods

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

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

IsoValue ByteString Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT ByteString :: T Source #

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

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Text :: T Source #

IsoValue MText Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT MText :: T Source #

IsoValue KeyHash Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT KeyHash :: T Source #

IsoValue Signature Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Signature :: T Source #

IsoValue PublicKey Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT PublicKey :: T Source #

IsoValue ChainId Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT ChainId :: T Source #

IsoValue Timestamp Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Timestamp :: T Source #

IsoValue Mutez Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Mutez :: T Source #

IsoValue Address Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Address :: T Source #

IsoValue EpAddress Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT EpAddress :: T Source #

IsoValue Operation Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Operation :: T Source #

IsoValue MyCompoundType Source # 
Instance details

Defined in Michelson.Typed.Haskell.Instr.Sum

Associated Types

type ToT MyCompoundType :: T Source #

IsoValue MigrationScript Source # 
Instance details

Defined in Lorentz.UStore.Migration.Base

Associated Types

type ToT MigrationScript :: T Source #

IsoValue UnspecifiedError Source # 
Instance details

Defined in Lorentz.Errors

Associated Types

type ToT UnspecifiedError :: T Source #

IsoValue a => IsoValue [a] Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT [a] :: T Source #

Methods

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

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

IsoValue a => IsoValue (Maybe a) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (Maybe a) :: T Source #

Methods

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

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

IsoValue a => IsoValue (Identity a) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (Identity a) :: T Source #

(Ord c, IsoCValue c) => IsoValue (Set c) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (Set c) :: T Source #

Methods

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

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

IsoValue (ContractRef arg) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (ContractRef arg) :: T Source #

IsoValue (UStore a) Source # 
Instance details

Defined in Lorentz.UStore.Types

Associated Types

type ToT (UStore a) :: T Source #

Methods

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

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

(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 Source #

(CustomErrorNoIsoValue (VoidResult r) :: Constraint) => IsoValue (VoidResult r) Source # 
Instance details

Defined in Lorentz.Macro

Associated Types

type ToT (VoidResult r) :: T Source #

IsoValue (UParam entries) Source # 
Instance details

Defined in Lorentz.UParam

Associated Types

type ToT (UParam entries) :: T Source #

Methods

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

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

IsoValue a => IsoValue (Store a) Source # 
Instance details

Defined in Lorentz.Store

Associated Types

type ToT (Store a) :: T Source #

Methods

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

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

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

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (Either l r) :: T Source #

Methods

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

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

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

Defined in Michelson.Typed.Haskell.Value

Associated Types

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

Methods

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

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

(Ord k, IsoCValue k, IsoValue v) => IsoValue (Map k v) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (Map k v) :: T Source #

Methods

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

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

(Ord k, IsoCValue k, IsoValue v) => IsoValue (BigMap k v) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (BigMap k v) :: T Source #

Methods

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

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

IsoValue (FutureContract p) Source # 
Instance details

Defined in Lorentz.Value

Associated Types

type ToT (FutureContract p) :: T Source #

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

Defined in Lorentz.Zip

Associated Types

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

Methods

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

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

IsoValue (Extensible x) Source # 
Instance details

Defined in Lorentz.Extensible

Associated Types

type ToT (Extensible x) :: T Source #

IsoValue a => IsoValue (Void_ a b) Source # 
Instance details

Defined in Lorentz.Macro

Associated Types

type ToT (Void_ a b) :: T Source #

Methods

toVal :: Void_ a b -> Value (ToT (Void_ a b)) Source #

fromVal :: Value (ToT (Void_ a b)) -> Void_ a b Source #

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

Defined in Lorentz.Macro

Associated Types

type ToT (View a r) :: T Source #

Methods

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

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

(IsoValue storeTemplate, IsoValue other) => IsoValue (StorageSkeleton storeTemplate other) Source # 
Instance details

Defined in Lorentz.Store

Associated Types

type ToT (StorageSkeleton storeTemplate other) :: T Source #

Methods

toVal :: StorageSkeleton storeTemplate other -> Value (ToT (StorageSkeleton storeTemplate other)) Source #

fromVal :: Value (ToT (StorageSkeleton storeTemplate other)) -> StorageSkeleton storeTemplate other Source #

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

Defined in Michelson.Typed.Haskell.Value

Associated Types

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

Methods

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

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

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

Defined in Michelson.Typed.Haskell.Value

Associated Types

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

Methods

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

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

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

Defined in Michelson.Typed.Haskell.Value

Associated Types

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

Methods

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

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

IsoValue v => IsoValue (k2 |-> v) Source # 
Instance details

Defined in Lorentz.Store

Associated Types

type ToT (k2 |-> v) :: T Source #

Methods

toVal :: (k2 |-> v) -> Value (ToT (k2 |-> v)) Source #

fromVal :: Value (ToT (k2 |-> v)) -> k2 |-> v Source #

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

Defined in Michelson.Typed.Haskell.Value

Associated Types

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

Methods

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

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

IsoValue (MUStore oldTemplate newTemplate remDiff touched) Source # 
Instance details

Defined in Lorentz.UStore.Migration.Base

Associated Types

type ToT (MUStore oldTemplate newTemplate remDiff touched) :: T Source #

Methods

toVal :: MUStore oldTemplate newTemplate remDiff touched -> Value (ToT (MUStore oldTemplate newTemplate remDiff touched)) Source #

fromVal :: Value (ToT (MUStore oldTemplate newTemplate remDiff touched)) -> MUStore oldTemplate newTemplate remDiff touched Source #

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

Defined in Michelson.Typed.Haskell.Value

Associated Types

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

Methods

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

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

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

Defined in Michelson.Typed.Haskell.Value

Associated Types

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

Methods

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

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

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

Defined in Michelson.Typed.Haskell.Value

Associated Types

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

Methods

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

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

class IsoCValue a where Source #

Isomorphism between Michelson primitive values and plain Haskell types.

Associated Types

type ToCT a :: CT Source #

Type function that converts a regular Haskell type into a comparable type (which has kind CT).

Methods

toCVal :: a -> CValue (ToCT a) Source #

Converts a single Haskell value into CVal representation.

fromCVal :: CValue (ToCT a) -> a Source #

Converts a CVal value into a single Haskell value.

Instances
IsoCValue Bool Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToCT Bool :: CT Source #

IsoCValue Integer Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToCT Integer :: CT Source #

IsoCValue Natural Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToCT Natural :: CT Source #

IsoCValue ByteString Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToCT ByteString :: CT Source #

(DoNotUseTextError :: Constraint) => IsoCValue Text Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToCT Text :: CT Source #

IsoCValue MText Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToCT MText :: CT Source #

IsoCValue KeyHash Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToCT KeyHash :: CT Source #

IsoCValue Timestamp Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToCT Timestamp :: CT Source #

IsoCValue Mutez Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToCT Mutez :: CT Source #

IsoCValue Address Source #

This instance erases reference to contract entrypoint! If this is an issue, use EpAddress instead.

Applications which use addresses just as participants identifiers should not experience problems with using plain Address.

Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToCT Address :: CT Source #

IsoCValue EpAddress Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToCT EpAddress :: CT Source #

data CValue t where Source #

Representation of comparable value in Michelson language.

By specification, we're allowed to compare only following types: int, nat, string, bytes, mutez, bool, key_hash, timestamp, address.

Only these values can be used as map keys or set elements.

Instances
Eq (CValue t) Source # 
Instance details

Defined in Michelson.Typed.CValue

Methods

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

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

Ord (CValue t) Source # 
Instance details

Defined in Michelson.Typed.CValue

Methods

compare :: CValue t -> CValue t -> Ordering #

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

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

(>) :: CValue t -> CValue t -> Bool #

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

max :: CValue t -> CValue t -> CValue t #

min :: CValue t -> CValue t -> CValue t #

Show (CValue t) Source # 
Instance details

Defined in Michelson.Typed.CValue

Methods

showsPrec :: Int -> CValue t -> ShowS #

show :: CValue t -> String #

showList :: [CValue t] -> ShowS #

Arbitrary (CValue CInt) Source # 
Instance details

Defined in Michelson.Test.Gen

Arbitrary (CValue CMutez) Source # 
Instance details

Defined in Michelson.Test.Gen

Arbitrary (CValue CKeyHash) Source # 
Instance details

Defined in Michelson.Test.Gen

Arbitrary (CValue CTimestamp) Source # 
Instance details

Defined in Michelson.Test.Gen

Primitive types

data Integer #

Invariant: Jn# and Jp# are used iff value doesn't fit in S#

Useful properties resulting from the invariants:

Instances
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

Data Integer

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

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

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

toConstr :: Integer -> Constr #

dataTypeOf :: Integer -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Ix Integer

Since: base-2.1

Instance details

Defined in GHC.Arr

Lift Integer 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Integer -> Q Exp #

Arbitrary Integer 
Instance details

Defined in Test.QuickCheck.Arbitrary

CoArbitrary Integer 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

coarbitrary :: Integer -> Gen b -> Gen b #

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

ToJSONKey Integer 
Instance details

Defined in Data.Aeson.Types.ToJSON

FromJSON Integer

This instance includes a bounds check to prevent maliciously large inputs to fill up the memory of the target system. You can newtype Scientific and provide your own instance using withScientific if you want to allow larger inputs.

Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Integer 
Instance details

Defined in Data.Aeson.Types.FromJSON

Bits Integer

Since: base-2.1

Instance details

Defined in Data.Bits

Subtractive Integer 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Integer :: Type #

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 #

Random Integer 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Integer, Integer) -> g -> (Integer, g) #

random :: RandomGen g => g -> (Integer, g) #

randomRs :: RandomGen g => (Integer, Integer) -> g -> [Integer] #

randoms :: RandomGen g => g -> [Integer] #

randomRIO :: (Integer, Integer) -> IO Integer #

randomIO :: IO Integer #

Pretty Integer 
Instance details

Defined in Text.PrettyPrint.Leijen.Text

Methods

pretty :: Integer -> Doc #

prettyList :: [Integer] -> Doc #

IsoValue Integer Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Integer :: T Source #

IsoCValue Integer Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToCT Integer :: CT Source #

TypeHasDoc Integer Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

CompareOpHs Integer Source # 
Instance details

Defined in Lorentz.Arith

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 Ge Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Ge Integer :: Type Source #

UnaryArithOpHs Le Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Le Integer :: Type Source #

UnaryArithOpHs Gt Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Gt Integer :: Type Source #

UnaryArithOpHs Lt Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Lt Integer :: Type Source #

UnaryArithOpHs Neq Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Neq Integer :: Type Source #

UnaryArithOpHs Eq' Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Eq' Integer :: Type Source #

UnaryArithOpHs Not Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Not Integer :: Type Source #

UnaryArithOpHs Neg Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Neg Integer :: Type Source #

UnaryArithOpHs Abs Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Abs Integer :: Type Source #

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

Defined in Data.Reflection

Methods

reflect :: proxy n -> Integer #

ArithOpHs And Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs And Integer Natural :: Type Source #

ArithOpHs Mul Integer Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Integer Integer :: Type Source #

ArithOpHs Mul Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Integer Natural :: Type Source #

ArithOpHs Mul Natural Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Natural Integer :: Type Source #

ArithOpHs Sub Integer Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Sub Integer Integer :: Type Source #

ArithOpHs Sub Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Sub Integer Natural :: Type Source #

ArithOpHs Sub Natural Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Sub Natural Integer :: Type Source #

ArithOpHs Sub Timestamp Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Sub Timestamp Integer :: Type Source #

ArithOpHs Add Integer Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Integer Integer :: Type Source #

ArithOpHs Add Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Integer Natural :: Type Source #

ArithOpHs Add Integer Timestamp Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Integer Timestamp :: Type Source #

ArithOpHs Add Natural Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Natural Integer :: Type Source #

ArithOpHs Add Timestamp Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Timestamp Integer :: Type 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 ToT Integer Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToCT Integer Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

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 Ge Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Le Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Gt Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Lt Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Neq Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Eq' Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Not Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Neg Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Abs 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 Natural 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

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

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
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

Data Natural

Since: base-4.8.0.0

Instance details

Defined in Data.Data

Methods

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

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

toConstr :: Natural -> Constr #

dataTypeOf :: Natural -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Ix Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Arr

Lift Natural 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Natural -> Q Exp #

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

ToJSONKey Natural 
Instance details

Defined in Data.Aeson.Types.ToJSON

FromJSON Natural 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Natural 
Instance details

Defined in Data.Aeson.Types.FromJSON

Bits Natural

Since: base-4.8.0

Instance details

Defined in Data.Bits

Subtractive Natural 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Natural :: Type #

NFData Natural

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Natural -> () #

Default Natural Source # 
Instance details

Defined in Util.Instances

Methods

def :: Natural #

Buildable Natural Source # 
Instance details

Defined in Util.Instances

Methods

build :: Natural -> Builder #

IsoValue Natural Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Natural :: T Source #

IsoCValue Natural Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToCT Natural :: CT Source #

TypeHasDoc Natural Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

CompareOpHs Natural Source # 
Instance details

Defined in Lorentz.Arith

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 Not Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Not Natural :: Type Source #

UnaryArithOpHs Neg Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Neg Natural :: Type Source #

ArithOpHs Lsr Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Lsr Natural Natural :: Type Source #

ArithOpHs Lsl Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Lsl Natural Natural :: Type Source #

ArithOpHs Xor Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Xor Natural Natural :: Type Source #

ArithOpHs And Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs And Integer Natural :: Type Source #

ArithOpHs And Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs And Natural Natural :: Type Source #

ArithOpHs Or Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Or Natural Natural :: Type Source #

ArithOpHs Mul Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Integer Natural :: Type Source #

ArithOpHs Mul Natural Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Natural Integer :: Type Source #

ArithOpHs Mul Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Natural Natural :: Type Source #

ArithOpHs Mul Natural Mutez Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Natural Mutez :: Type Source #

ArithOpHs Mul Mutez Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Mutez Natural :: Type Source #

ArithOpHs Sub Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Sub Integer Natural :: Type Source #

ArithOpHs Sub Natural Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Sub Natural Integer :: Type Source #

ArithOpHs Sub Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Sub Natural Natural :: Type Source #

ArithOpHs Add Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Integer Natural :: Type Source #

ArithOpHs Add Natural Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Natural Integer :: Type Source #

ArithOpHs Add Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Natural Natural :: Type 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 ToT Natural Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToCT Natural Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

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 Not Natural Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Neg Natural Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Lsr Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Lsl Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Xor 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 Or 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 Mutez Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Mul Mutez 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 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

data MText Source #

Michelson string value.

This is basically a mere text with limits imposed by the language: http://tezos.gitlab.io/zeronet/whitedoc/michelson.html#constants Although, this document seems to be not fully correct, and thus we applied constraints deduced empirically.

You construct an item of this type using one of the following ways:

  • With QuasyQuotes when need to create a string literal.
>>> [mt|Some text|]
MTextUnsafe { unMText = "Some text" }
  • With mkMText when constructing from a runtime text value.
  • With mkMTextUnsafe or MTextUnsafe when absolutelly sure that given string does not violate invariants.
  • With mkMTextCut when not sure about text contents and want to make it compliant with Michelson constraints.
Instances
Eq MText Source # 
Instance details

Defined in Michelson.Text

Methods

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

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

Data MText Source # 
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 :: (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 Source # 
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 Source # 
Instance details

Defined in Michelson.Text

Methods

showsPrec :: Int -> MText -> ShowS #

show :: MText -> String #

showList :: [MText] -> ShowS #

(TypeError (Text "There is no instance defined for (IsString MText)" :$$: Text "Consider using QuasiQuotes: `[mt|some text...|]`") :: Constraint) => IsString MText Source # 
Instance details

Defined in Michelson.Text

Methods

fromString :: String -> MText #

Semigroup MText Source # 
Instance details

Defined in Michelson.Text

Methods

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

sconcat :: NonEmpty MText -> MText #

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

Monoid MText Source # 
Instance details

Defined in Michelson.Text

Methods

mempty :: MText #

mappend :: MText -> MText -> MText #

mconcat :: [MText] -> MText #

Arbitrary MText Source # 
Instance details

Defined in Michelson.Text

Methods

arbitrary :: Gen MText #

shrink :: MText -> [MText] #

Hashable MText Source # 
Instance details

Defined in Michelson.Text

Methods

hashWithSalt :: Int -> MText -> Int #

hash :: MText -> Int #

ToJSON MText Source # 
Instance details

Defined in Michelson.Text

FromJSON MText Source # 
Instance details

Defined in Michelson.Text

Buildable MText Source # 
Instance details

Defined in Michelson.Text

Methods

build :: MText -> Builder #

Container MText Source # 
Instance details

Defined in Michelson.Text

Associated Types

type Element MText :: Type #

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

ToText MText Source # 
Instance details

Defined in Michelson.Text

Methods

toText :: MText -> Text #

IsoValue MText Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT MText :: T Source #

IsoCValue MText Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToCT MText :: CT Source #

TypeHasDoc MText Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

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

CompareOpHs MText Source # 
Instance details

Defined in Lorentz.Arith

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 :: (Typeable t, SingI t) => Value t -> Either Text MText Source #

ErrorHasDoc MText Source # 
Instance details

Defined in Lorentz.Errors

type Element MText Source # 
Instance details

Defined in Michelson.Text

type ToT MText Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT MText = Tc (ToCT MText)
type ToCT MText Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

data Bool #

Constructors

False 
True 
Instances
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 #

Data Bool

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

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

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

toConstr :: Bool -> Constr #

dataTypeOf :: Bool -> DataType #

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

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

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

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

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

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

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

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

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

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bool -> m 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 #

Ix Bool

Since: base-2.1

Instance details

Defined in GHC.Arr

Methods

range :: (Bool, Bool) -> [Bool] #

index :: (Bool, Bool) -> Bool -> Int #

unsafeIndex :: (Bool, Bool) -> Bool -> Int

inRange :: (Bool, Bool) -> Bool -> Bool #

rangeSize :: (Bool, Bool) -> Int #

unsafeRangeSize :: (Bool, Bool) -> Int

Generic Bool 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Bool :: Type -> Type #

Methods

from :: Bool -> Rep Bool x #

to :: Rep Bool x -> Bool #

Lift Bool 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Bool -> Q Exp #

Testable Bool 
Instance details

Defined in Test.QuickCheck.Property

Methods

property :: Bool -> Property #

propertyForAllShrinkShow :: Gen a -> (a -> [a]) -> (a -> [String]) -> (a -> Bool) -> Property #

Arbitrary Bool 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen Bool #

shrink :: Bool -> [Bool] #

CoArbitrary Bool 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

coarbitrary :: Bool -> Gen b -> Gen b #

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

FromJSON Bool 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Bool 
Instance details

Defined in Data.Aeson.Types.FromJSON

SingKind Bool

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type DemoteRep Bool :: Type

Methods

fromSing :: Sing a -> DemoteRep Bool

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 () #

Bits Bool

Interpret Bool as 1-bit bit-field

Since: base-4.7.0.0

Instance details

Defined in Data.Bits

FiniteBits Bool

Since: base-4.7.0.0

Instance details

Defined in Data.Bits

NFData Bool 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Bool -> () #

Buildable Bool 
Instance details

Defined in Formatting.Buildable

Methods

build :: Bool -> Builder #

Example Bool 
Instance details

Defined in Test.Hspec.Core.Example

Associated Types

type Arg Bool :: Type #

Unbox Bool 
Instance details

Defined in Data.Vector.Unboxed.Base

Random Bool 
Instance details

Defined in System.Random

Methods

randomR :: RandomGen g => (Bool, Bool) -> g -> (Bool, g) #

random :: RandomGen g => g -> (Bool, g) #

randomRs :: RandomGen g => (Bool, Bool) -> g -> [Bool] #

randoms :: RandomGen g => g -> [Bool] #

randomRIO :: (Bool, Bool) -> IO Bool #

randomIO :: IO 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 :: Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply ShowsPrecSym0 t1) t2) t3) #

sShow_ :: Sing t -> Sing (Apply Show_Sym0 t) #

sShowList :: 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

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 :: Sing t1 -> Sing t2 -> Sing (Apply (Apply CompareSym0 t1) t2) #

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

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

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

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

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

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

SEq Bool 
Instance details

Defined in Data.Singletons.Prelude.Eq

Methods

(%==) :: Sing a -> Sing b -> Sing (a == b) #

(%/=) :: 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 #

AssertionPredicable Bool 
Instance details

Defined in Test.Tasty.HUnit.Orig

Assertable Bool 
Instance details

Defined in Test.Tasty.HUnit.Orig

Methods

assert :: Bool -> Assertion #

Pretty Bool 
Instance details

Defined in Text.PrettyPrint.Leijen.Text

Methods

pretty :: Bool -> Doc #

prettyList :: [Bool] -> Doc #

IsoValue Bool Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Bool :: T Source #

IsoCValue Bool Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToCT Bool :: CT Source #

TypeHasDoc Bool Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

CompareOpHs Bool Source # 
Instance details

Defined in Lorentz.Arith

IArray UArray Bool 
Instance details

Defined in Data.Array.Base

Methods

bounds :: Ix i => UArray i Bool -> (i, i) #

numElements :: Ix i => UArray i Bool -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Bool)] -> UArray i Bool

unsafeAt :: Ix i => UArray i Bool -> Int -> Bool

unsafeReplace :: Ix i => UArray i Bool -> [(Int, Bool)] -> UArray i Bool

unsafeAccum :: Ix i => (Bool -> e' -> Bool) -> UArray i Bool -> [(Int, e')] -> UArray i Bool

unsafeAccumArray :: Ix i => (Bool -> e' -> Bool) -> Bool -> (i, i) -> [(Int, e')] -> UArray i Bool

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

Vector Vector Bool 
Instance details

Defined in Data.Vector.Unboxed.Base

Showtype False 
Instance details

Defined in Type.Showtype

Methods

showtype :: proxy False -> String #

showtypesPrec :: Int -> proxy False -> String -> String #

Showtype True 
Instance details

Defined in Type.Showtype

Methods

showtype :: proxy True -> String #

showtypesPrec :: Int -> proxy True -> String -> String #

MVector MVector Bool 
Instance details

Defined in Data.Vector.Unboxed.Base

UnaryArithOpHs Not Bool Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Not Bool :: Type Source #

ArithOpHs Xor Bool Bool Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Xor Bool Bool :: Type Source #

ArithOpHs And Bool Bool Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs And Bool Bool :: Type Source #

ArithOpHs Or Bool Bool Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Or Bool Bool :: Type 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 #

MArray (STUArray s) Bool (ST s) 
Instance details

Defined in Data.Array.Base

Methods

getBounds :: Ix i => STUArray s i Bool -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Bool -> ST s Int

newArray :: Ix i => (i, i) -> Bool -> ST s (STUArray s i Bool) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Bool) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Bool)

unsafeRead :: Ix i => STUArray s i Bool -> Int -> ST s Bool

unsafeWrite :: Ix i => STUArray s i Bool -> Int -> Bool -> ST s ()

Example (a -> Bool) 
Instance details

Defined in Test.Hspec.Core.Example

Associated Types

type Arg (a -> Bool) :: Type #

Methods

evaluateExample :: (a -> Bool) -> Params -> (ActionWith (Arg (a -> Bool)) -> IO ()) -> ProgressCallback -> IO Result #

SuppressUnusedWarnings NotSym0 
Instance details

Defined in Data.Singletons.Prelude.Bool

SuppressUnusedWarnings FromEnum_6989586621679763238Sym0 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings AllSym0 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

SuppressUnusedWarnings All_Sym0 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

SuppressUnusedWarnings AnySym0 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

SuppressUnusedWarnings Any_Sym0 
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_6989586621679390848Sym0 
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_6989586621679763232Sym0 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings ShowsPrec_6989586621680280441Sym0 
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 AllSym0 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

sing :: Sing AllSym0 #

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 #

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

Defined in Data.Singletons.Prelude.Bool

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

Defined in Data.Singletons.Prelude.Bool

SuppressUnusedWarnings (Compare_6989586621679390848Sym1 a6989586621679390846 :: TyFun Bool Ordering -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (ShowsPrec_6989586621680280441Sym1 a6989586621680280438 :: TyFun Bool (Symbol ~> Symbol) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Show

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

Defined in Data.Singletons.Prelude.Monad.Internal

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

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

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

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

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.Maybe

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

Defined in Data.Singletons.Prelude.Maybe

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

Defined in Data.Singletons.TypeLits.Internal

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

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

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680450690Scrutinee_6989586621680450448Sym0 :: TyFun (t6989586621680450201 Bool) All -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680450681Scrutinee_6989586621680450450Sym0 :: TyFun (t6989586621680450201 Bool) Any -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Eq

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

Defined in Data.Singletons.Prelude.Eq

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

Defined in Data.Singletons.Prelude.Eq

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

Defined in Data.Singletons.Prelude.Bool

SuppressUnusedWarnings (TFHelper_6989586621679379660Sym0 :: TyFun a6989586621679379451 (a6989586621679379451 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (TFHelper_6989586621679379642Sym0 :: TyFun a6989586621679379451 (a6989586621679379451 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (TFHelper_6989586621679379624Sym0 :: TyFun a6989586621679379451 (a6989586621679379451 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (TFHelper_6989586621679379606Sym0 :: TyFun a6989586621679379451 (a6989586621679379451 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (Elem_6989586621680675575Sym0 :: TyFun a6989586621680450218 (Identity a6989586621680450218 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Identity

SuppressUnusedWarnings (Null_6989586621680675698Sym0 :: TyFun (Identity a6989586621680450216) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Identity

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (UntilSym0 :: TyFun (a6989586621679519853 ~> Bool) ((a6989586621679519853 ~> a6989586621679519853) ~> (a6989586621679519853 ~> a6989586621679519853)) -> 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 (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 a6989586621680387800 :: TyFun [a6989586621680386748] Bool -> Type) 
Instance details

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

SuppressUnusedWarnings (ListelemSym1 a6989586621680387735 :: TyFun [a6989586621680386736] Bool -> Type) 
Instance details

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

SuppressUnusedWarnings (NotElemSym1 a6989586621679949109 :: TyFun [a6989586621679939225] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (IsSuffixOfSym1 a6989586621679949734 :: TyFun [a6989586621679939228] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (IsPrefixOfSym1 a6989586621679949143 :: TyFun [a6989586621679939229] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (IsInfixOfSym1 a6989586621679949381 :: TyFun [a6989586621679939227] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (ElemSym1 a6989586621679949116 :: TyFun [a6989586621679939226] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (AnySym1 a6989586621679949374 :: TyFun [a6989586621679939246] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (AllSym1 a6989586621679949429 :: TyFun [a6989586621679939247] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (IsRightSym0 :: TyFun (Either a6989586621680431647 b6989586621680431648) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Either

SuppressUnusedWarnings (IsLeftSym0 :: TyFun (Either a6989586621680431649 b6989586621680431650) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Either

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

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Elem_bySym1 a6989586621679948401 :: TyFun a6989586621679939143 ([a6989586621679939143] ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (NotElemSym0 :: TyFun a6989586621680450112 (t6989586621680450111 a6989586621680450112 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680451921Sym0 :: TyFun a6989586621680450218 (t6989586621680450201 a6989586621680450218 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680451754Sym0 :: TyFun a6989586621680450218 (t6989586621680450201 a6989586621680450218 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680451587Sym0 :: TyFun a6989586621680450218 (t6989586621680450201 a6989586621680450218 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680451250Sym0 :: TyFun a6989586621680450218 (t6989586621680450201 a6989586621680450218 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680451127Sym0 :: TyFun a6989586621680450218 (t6989586621680450201 a6989586621680450218 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (ElemSym0 :: TyFun a6989586621680450218 (t6989586621680450201 a6989586621680450218 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (DefaultEqSym1 a6989586621679363165 :: TyFun k6989586621679363164 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Eq

SuppressUnusedWarnings ((==@#@$$) x6989586621679363171 :: TyFun a6989586621679363170 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Eq

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

Defined in Data.Singletons.Prelude.Eq

SuppressUnusedWarnings (Bool_Sym1 a6989586621679359156 :: TyFun a6989586621679359150 (Bool ~> a6989586621679359150) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Bool

SuppressUnusedWarnings (TFHelper_6989586621679379660Sym1 a6989586621679379658 :: TyFun a6989586621679379451 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (TFHelper_6989586621679379642Sym1 a6989586621679379640 :: TyFun a6989586621679379451 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (TFHelper_6989586621679379624Sym1 a6989586621679379622 :: TyFun a6989586621679379451 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (TFHelper_6989586621679379606Sym1 a6989586621679379604 :: TyFun a6989586621679379451 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings ((>@#@$$) arg6989586621679379552 :: TyFun a6989586621679379451 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings ((>=@#@$$) arg6989586621679379556 :: TyFun a6989586621679379451 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings ((<@#@$$) arg6989586621679379544 :: TyFun a6989586621679379451 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (TFHelper_6989586621680882327Sym0 :: TyFun (Arg a6989586621680881110 b6989586621680881111) (Arg a6989586621680881110 b6989586621680881111 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

SuppressUnusedWarnings (Elem_6989586621680675575Sym1 a6989586621680675573 :: TyFun (Identity a6989586621680450218) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Identity

SuppressUnusedWarnings (Let6989586621679948659ZsSym0 :: TyFun (k1 ~> (a6989586621679939166 ~> Bool)) (TyFun k1 (TyFun [a6989586621679939166] [a6989586621679939166] -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621679948659YsSym0 :: TyFun (k1 ~> (a6989586621679939166 ~> Bool)) (TyFun k1 (TyFun [a6989586621679939166] [a6989586621679939166] -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621679948417NubBy'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_6989586621679949750Sym0 :: TyFun (a6989586621679939263 ~> Bool) (TyFun k (TyFun a6989586621679939263 (TyFun [a6989586621679939263] [a6989586621679939263] -> Type) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680450671Scrutinee_6989586621680450452Sym0 :: TyFun (a6989586621680450204 ~> Bool) (TyFun (t6989586621680450201 a6989586621680450204) Any -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680450658Scrutinee_6989586621680450454Sym0 :: TyFun (a6989586621680450204 ~> Bool) (TyFun (t6989586621680450201 a6989586621680450204) All -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680450573Scrutinee_6989586621680450460Sym0 :: TyFun (a6989586621680450204 ~> Bool) (TyFun (t6989586621680450201 a6989586621680450204) (First a6989586621680450204) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Lambda_6989586621680450574Sym0 :: TyFun (a6989586621679072633 ~> Bool) (TyFun k (TyFun a6989586621679072633 (First a6989586621679072633) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (FindSym0 :: TyFun (a6989586621680450110 ~> Bool) (t6989586621680450109 a6989586621680450110 ~> Maybe a6989586621680450110) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (AnySym0 :: TyFun (a6989586621680450120 ~> Bool) (t6989586621680450119 a6989586621680450120 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (AllSym0 :: TyFun (a6989586621680450118 ~> Bool) (t6989586621680450117 a6989586621680450118 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621679519989GoSym0 :: TyFun (k2 ~> Bool) (TyFun (k2 ~> k2) (TyFun k1 (TyFun k2 k2 -> 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) #

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 a6989586621679359157 a6989586621679359156 :: TyFun Bool a6989586621679359150 -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Bool

SuppressUnusedWarnings (Elem_bySym2 a6989586621679948402 a6989586621679948401 :: TyFun [a6989586621679939143] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621679948456Scrutinee_6989586621679939844Sym1 n6989586621679948454 :: TyFun k Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Null_6989586621680452044Sym0 :: TyFun (t6989586621680450201 a6989586621680450216) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Null_6989586621680451877Sym0 :: TyFun (t6989586621680450201 a6989586621680450216) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Null_6989586621680451710Sym0 :: TyFun (t6989586621680450201 a6989586621680450216) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Null_6989586621680451564Sym0 :: TyFun (t6989586621680450201 a6989586621680450216) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Null_6989586621680451388Sym0 :: TyFun (t6989586621680450201 a6989586621680450216) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Null_6989586621680451090Sym0 :: TyFun (t6989586621680450201 a6989586621680450216) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (NullSym0 :: TyFun (t6989586621680450201 a6989586621680450216) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (NotElemSym1 a6989586621680450594 t6989586621680450111 :: TyFun (t6989586621680450111 a6989586621680450112) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680451921Sym1 a6989586621680451919 t6989586621680450201 :: TyFun (t6989586621680450201 a6989586621680450218) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680451754Sym1 a6989586621680451752 t6989586621680450201 :: TyFun (t6989586621680450201 a6989586621680450218) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680451587Sym1 a6989586621680451585 t6989586621680450201 :: TyFun (t6989586621680450201 a6989586621680450218) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680451250Sym1 a6989586621680451248 t6989586621680450201 :: TyFun (t6989586621680450201 a6989586621680450218) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680451127Sym1 a6989586621680451125 t6989586621680450201 :: TyFun (t6989586621680450201 a6989586621680450218) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (ElemSym1 arg6989586621680450868 t6989586621680450201 :: TyFun (t6989586621680450201 a6989586621680450218) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (AnySym1 a6989586621680450665 t6989586621680450119 :: TyFun (t6989586621680450119 a6989586621680450120) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (AllSym1 a6989586621680450652 t6989586621680450117 :: TyFun (t6989586621680450117 a6989586621680450118) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (TFHelper_6989586621680882327Sym1 a6989586621680882325 :: TyFun (Arg a6989586621680881110 b6989586621680881111) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

(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 t :: TyFun (t a) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (NotElemSym1 d t) #

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

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (ElemSym1 d t) #

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

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (AnySym1 d t) #

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

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (AllSym1 d t) #

SuppressUnusedWarnings (Let6989586621679949754Scrutinee_6989586621679939822Sym1 p6989586621679949748 :: TyFun k1 (TyFun [a6989586621679939263] (TyFun k Bool -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621679949135Scrutinee_6989586621679939848Sym1 l6989586621679949125 :: TyFun k2 (TyFun k1 (TyFun [k2] Bool -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621679948553Scrutinee_6989586621679939828Sym1 n6989586621679948550 :: TyFun k1 (TyFun k2 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621679948539Scrutinee_6989586621679939830Sym1 n6989586621679948536 :: TyFun k1 (TyFun k2 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621679948443Scrutinee_6989586621679939846Sym1 x6989586621679948440 :: TyFun k1 (TyFun k2 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Lambda_6989586621680451077Sym1 a_69895866216804510726989586621680451076 :: TyFun k1 (TyFun k2 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621679949754Scrutinee_6989586621679939822Sym2 x6989586621679949752 p6989586621679949748 :: TyFun [a6989586621679939263] (TyFun k Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621679949135Scrutinee_6989586621679939848Sym2 x6989586621679949132 l6989586621679949125 :: TyFun k1 (TyFun [k2] Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621679948553Scrutinee_6989586621679939828Sym2 x6989586621679948551 n6989586621679948550 :: TyFun k1 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621679948539Scrutinee_6989586621679939830Sym2 x6989586621679948537 n6989586621679948536 :: TyFun k1 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621679948524Scrutinee_6989586621679939840Sym2 x6989586621679948521 key6989586621679948520 :: TyFun k1 (TyFun k2 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621679948443Scrutinee_6989586621679939846Sym2 xs6989586621679948441 x6989586621679948440 :: TyFun k1 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621679948427Scrutinee_6989586621679939850Sym2 l6989586621679948416 eq6989586621679948415 :: TyFun k3 (TyFun k1 (TyFun [k3] Bool -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Lambda_6989586621680451077Sym2 t6989586621680451084 a_69895866216804510726989586621680451076 :: TyFun k1 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Enum

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

Defined in Data.Singletons.Prelude.Enum

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

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Lambda_6989586621679949409Sym0 :: TyFun (b6989586621679544177 ~> (a6989586621679939246 ~> Bool)) (TyFun k1 (TyFun k2 (TyFun a6989586621679939246 (TyFun [a6989586621679939246] (TyFun b6989586621679544177 (m6989586621679544173 b6989586621679544177) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621679949135Scrutinee_6989586621679939848Sym3 xs6989586621679949133 x6989586621679949132 l6989586621679949125 :: TyFun [k2] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621679949754Scrutinee_6989586621679939822Sym3 xs6989586621679949753 x6989586621679949752 p6989586621679949748 :: TyFun k Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621679948524Scrutinee_6989586621679939840Sym3 y6989586621679948522 x6989586621679948521 key6989586621679948520 :: TyFun k1 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621679948427Scrutinee_6989586621679939850Sym3 y6989586621679948424 l6989586621679948416 eq6989586621679948415 :: TyFun k1 (TyFun [k3] Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621679739617Scrutinee_6989586621679739383Sym2 y6989586621679739608 x06989586621679739607 :: TyFun k3 (TyFun k1 (TyFun k2 Bool -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

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

Defined in Data.Singletons.Prelude.Enum

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

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621679948427Scrutinee_6989586621679939850Sym4 ys6989586621679948425 y6989586621679948424 l6989586621679948416 eq6989586621679948415 :: TyFun [k3] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621679739617Scrutinee_6989586621679739383Sym3 x6989586621679739616 y6989586621679739608 x06989586621679739607 :: TyFun k1 (TyFun k2 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621679739540Scrutinee_6989586621679739397Sym2 x26989586621679739536 x16989586621679739535 :: TyFun k5 (TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621679739483Scrutinee_6989586621679739407Sym2 x26989586621679739479 x16989586621679739478 :: TyFun k5 (TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621679739617Scrutinee_6989586621679739383Sym4 arg_69895866216797393796989586621679739603 x6989586621679739616 y6989586621679739608 x06989586621679739607 :: TyFun k1 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621679739540Scrutinee_6989586621679739397Sym3 y6989586621679739537 x26989586621679739536 x16989586621679739535 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621679739483Scrutinee_6989586621679739407Sym3 y6989586621679739480 x26989586621679739479 x16989586621679739478 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621679739540Scrutinee_6989586621679739397Sym4 arg_69895866216797393916989586621679739530 y6989586621679739537 x26989586621679739536 x16989586621679739535 :: TyFun k1 (TyFun k2 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621679739483Scrutinee_6989586621679739407Sym4 arg_69895866216797394016989586621679739473 y6989586621679739480 x26989586621679739479 x16989586621679739478 :: TyFun k1 (TyFun k2 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621679739540Scrutinee_6989586621679739397Sym5 arg_69895866216797393936989586621679739531 arg_69895866216797393916989586621679739530 y6989586621679739537 x26989586621679739536 x16989586621679739535 :: TyFun k1 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621679739483Scrutinee_6989586621679739407Sym5 arg_69895866216797394036989586621679739474 arg_69895866216797394016989586621679739473 y6989586621679739480 x26989586621679739479 x16989586621679739478 :: TyFun k1 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Rep Bool

Since: base-4.6.0.0

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))
data Sing (a :: Bool) 
Instance details

Defined in GHC.Generics

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

Defined in GHC.Generics

type DemoteRep Bool = Bool
type Arg Bool 
Instance details

Defined in Test.Hspec.Core.Example

type Arg Bool = ()
newtype Vector Bool 
Instance details

Defined in Data.Vector.Unboxed.Base

type MaxBound 
Instance details

Defined in Data.Singletons.Prelude.Enum

type MaxBound = MaxBound_6989586621679735370Sym0
type MinBound 
Instance details

Defined in Data.Singletons.Prelude.Enum

type MinBound = MinBound_6989586621679735368Sym0
data Sing (a :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

type ToT Bool Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT Bool = Tc (ToCT Bool)
type ToCT Bool Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToCT Bool = CBool
type Show_ (arg :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Show

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

Defined in Data.Singletons.Prelude.Enum

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

Defined in Data.Singletons.Prelude.Enum

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

Defined in Data.Singletons.Prelude.Enum

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

Defined in Data.Singletons.Prelude.Enum

type Succ (arg :: Bool) = Apply (Succ_6989586621679739660Sym0 :: TyFun Bool Bool -> Type) arg
newtype MVector s Bool 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Bool = MV_Bool (MVector s Word8)
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_6989586621680262202Sym0 :: 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_6989586621679739680Sym0 :: 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_6989586621679379696Sym0 :: 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_6989586621679379678Sym0 :: 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_6989586621679379660Sym0 :: 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_6989586621679379642Sym0 :: 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_6989586621679379624Sym0 :: 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_6989586621679379606Sym0 :: 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_6989586621679390848Sym0 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_6989586621679364596 a b
type ArithResHs Xor Bool Bool Source # 
Instance details

Defined in Lorentz.Arith

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 ShowsPrec a1 (a2 :: Bool) a3 
Instance details

Defined in Data.Singletons.Prelude.Show

type ShowsPrec a1 (a2 :: Bool) a3 = Apply (Apply (Apply ShowsPrec_6989586621680280441Sym0 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_6989586621679739696Sym0 :: TyFun Bool (Bool ~> (Bool ~> [Bool])) -> Type) arg1) arg2) arg3
type Apply NotSym0 (a6989586621679360442 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Bool

type Apply NotSym0 (a6989586621679360442 :: Bool) = Not a6989586621679360442
type Apply ToEnum_6989586621679763232Sym0 (a6989586621679763231 :: Nat) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply ToEnum_6989586621679763232Sym0 (a6989586621679763231 :: Nat) = ToEnum_6989586621679763232 a6989586621679763231
type Apply GetAllSym0 (a6989586621679819675 :: All) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply GetAllSym0 (a6989586621679819675 :: All) = GetAll a6989586621679819675
type Apply GetAnySym0 (a6989586621679819689 :: Any) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply GetAnySym0 (a6989586621679819689 :: Any) = GetAny a6989586621679819689
type Apply FromEnum_6989586621679763238Sym0 (a6989586621679763237 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply FromEnum_6989586621679763238Sym0 (a6989586621679763237 :: Bool) = FromEnum_6989586621679763238 a6989586621679763237
type Apply All_Sym0 (a6989586621679852529 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply All_Sym0 (a6989586621679852529 :: Bool) = All_ a6989586621679852529
type Apply AllSym0 (t6989586621679819678 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply AllSym0 (t6989586621679819678 :: Bool) = All t6989586621679819678
type Apply Any_Sym0 (a6989586621679852528 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply Any_Sym0 (a6989586621679852528 :: Bool) = Any_ a6989586621679852528
type Apply AnySym0 (t6989586621679819692 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply AnySym0 (t6989586621679819692 :: Bool) = Any t6989586621679819692
type Apply ((||@#@$$) a6989586621679360142 :: TyFun Bool Bool -> Type) (b6989586621679360143 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Bool

type Apply ((||@#@$$) a6989586621679360142 :: TyFun Bool Bool -> Type) (b6989586621679360143 :: Bool) = a6989586621679360142 || b6989586621679360143
type Apply ((&&@#@$$) a6989586621679359901 :: TyFun Bool Bool -> Type) (b6989586621679359902 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Bool

type Apply ((&&@#@$$) a6989586621679359901 :: TyFun Bool Bool -> Type) (b6989586621679359902 :: Bool) = a6989586621679359901 && b6989586621679359902
type Apply ((<=?@#@$$) a3530822107858468865 :: TyFun Nat Bool -> Type) (b3530822107858468866 :: Nat) 
Instance details

Defined in Data.Singletons.TypeLits.Internal

type Apply ((<=?@#@$$) a3530822107858468865 :: TyFun Nat Bool -> Type) (b3530822107858468866 :: Nat) = a3530822107858468865 <=? b3530822107858468866
type Apply (Compare_6989586621679390848Sym1 a6989586621679390846 :: TyFun Bool Ordering -> Type) (a6989586621679390847 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Compare_6989586621679390848Sym1 a6989586621679390846 :: TyFun Bool Ordering -> Type) (a6989586621679390847 :: Bool) = Compare_6989586621679390848 a6989586621679390846 a6989586621679390847
type Apply (Let6989586621680441997Scrutinee_6989586621680441960Sym1 x6989586621680441990 :: TyFun k1 Bool -> Type) (y6989586621680441991 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680441997Scrutinee_6989586621680441960Sym1 x6989586621680441990 :: TyFun k1 Bool -> Type) (y6989586621680441991 :: k1) = Let6989586621680441997Scrutinee_6989586621680441960 x6989586621680441990 y6989586621680441991
type Apply (Let6989586621680442024Scrutinee_6989586621680441962Sym1 x6989586621680442017 :: TyFun k1 Bool -> Type) (y6989586621680442018 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680442024Scrutinee_6989586621680441962Sym1 x6989586621680442017 :: TyFun k1 Bool -> Type) (y6989586621680442018 :: k1) = Let6989586621680442024Scrutinee_6989586621680441962 x6989586621680442017 y6989586621680442018
type Apply ((==@#@$$) x6989586621679363171 :: TyFun a Bool -> Type) (y6989586621679363172 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Eq

type Apply ((==@#@$$) x6989586621679363171 :: TyFun a Bool -> Type) (y6989586621679363172 :: a) = x6989586621679363171 == y6989586621679363172
type Apply ((/=@#@$$) x6989586621679363173 :: TyFun a Bool -> Type) (y6989586621679363174 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Eq

type Apply ((/=@#@$$) x6989586621679363173 :: TyFun a Bool -> Type) (y6989586621679363174 :: a) = x6989586621679363173 /= y6989586621679363174
type Apply (DefaultEqSym1 a6989586621679363165 :: TyFun k Bool -> Type) (b6989586621679363166 :: k) 
Instance details

Defined in Data.Singletons.Prelude.Eq

type Apply (DefaultEqSym1 a6989586621679363165 :: TyFun k Bool -> Type) (b6989586621679363166 :: k) = DefaultEq a6989586621679363165 b6989586621679363166
type Apply (Let6989586621679379574Scrutinee_6989586621679379469Sym1 x6989586621679379572 :: TyFun k1 Bool -> Type) (y6989586621679379573 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Let6989586621679379574Scrutinee_6989586621679379469Sym1 x6989586621679379572 :: TyFun k1 Bool -> Type) (y6989586621679379573 :: k1) = Let6989586621679379574Scrutinee_6989586621679379469 x6989586621679379572 y6989586621679379573
type Apply (TFHelper_6989586621679379660Sym1 a6989586621679379658 :: TyFun a Bool -> Type) (a6989586621679379659 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (TFHelper_6989586621679379660Sym1 a6989586621679379658 :: TyFun a Bool -> Type) (a6989586621679379659 :: a) = TFHelper_6989586621679379660 a6989586621679379658 a6989586621679379659
type Apply (TFHelper_6989586621679379642Sym1 a6989586621679379640 :: TyFun a Bool -> Type) (a6989586621679379641 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (TFHelper_6989586621679379642Sym1 a6989586621679379640 :: TyFun a Bool -> Type) (a6989586621679379641 :: a) = TFHelper_6989586621679379642 a6989586621679379640 a6989586621679379641
type Apply (TFHelper_6989586621679379624Sym1 a6989586621679379622 :: TyFun a Bool -> Type) (a6989586621679379623 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (TFHelper_6989586621679379624Sym1 a6989586621679379622 :: TyFun a Bool -> Type) (a6989586621679379623 :: a) = TFHelper_6989586621679379624 a6989586621679379622 a6989586621679379623
type Apply (TFHelper_6989586621679379606Sym1 a6989586621679379604 :: TyFun a Bool -> Type) (a6989586621679379605 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (TFHelper_6989586621679379606Sym1 a6989586621679379604 :: TyFun a Bool -> Type) (a6989586621679379605 :: a) = TFHelper_6989586621679379606 a6989586621679379604 a6989586621679379605
type Apply ((<=@#@$$) arg6989586621679379548 :: TyFun a Bool -> Type) (arg6989586621679379549 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply ((<=@#@$$) arg6989586621679379548 :: TyFun a Bool -> Type) (arg6989586621679379549 :: a) = arg6989586621679379548 <= arg6989586621679379549
type Apply ((>=@#@$$) arg6989586621679379556 :: TyFun a Bool -> Type) (arg6989586621679379557 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply ((>=@#@$$) arg6989586621679379556 :: TyFun a Bool -> Type) (arg6989586621679379557 :: a) = arg6989586621679379556 >= arg6989586621679379557
type Apply ((>@#@$$) arg6989586621679379552 :: TyFun a Bool -> Type) (arg6989586621679379553 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply ((>@#@$$) arg6989586621679379552 :: TyFun a Bool -> Type) (arg6989586621679379553 :: a) = arg6989586621679379552 > arg6989586621679379553
type Apply (Let6989586621679379688Scrutinee_6989586621679379483Sym1 x6989586621679379686 :: TyFun k1 Bool -> Type) (y6989586621679379687 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Let6989586621679379688Scrutinee_6989586621679379483Sym1 x6989586621679379686 :: TyFun k1 Bool -> Type) (y6989586621679379687 :: k1) = Let6989586621679379688Scrutinee_6989586621679379483 x6989586621679379686 y6989586621679379687
type Apply (Let6989586621679379670Scrutinee_6989586621679379481Sym1 x6989586621679379668 :: TyFun k1 Bool -> Type) (y6989586621679379669 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Let6989586621679379670Scrutinee_6989586621679379481Sym1 x6989586621679379668 :: TyFun k1 Bool -> Type) (y6989586621679379669 :: k1) = Let6989586621679379670Scrutinee_6989586621679379481 x6989586621679379668 y6989586621679379669
type Apply (Let6989586621679379579Scrutinee_6989586621679379471Sym1 x6989586621679379572 :: TyFun k1 Bool -> Type) (y6989586621679379573 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Let6989586621679379579Scrutinee_6989586621679379471Sym1 x6989586621679379572 :: TyFun k1 Bool -> Type) (y6989586621679379573 :: k1) = Let6989586621679379579Scrutinee_6989586621679379471 x6989586621679379572 y6989586621679379573
type Apply ((<@#@$$) arg6989586621679379544 :: TyFun a Bool -> Type) (arg6989586621679379545 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply ((<@#@$$) arg6989586621679379544 :: TyFun a Bool -> Type) (arg6989586621679379545 :: a) = arg6989586621679379544 < arg6989586621679379545
type Apply (Let6989586621679948456Scrutinee_6989586621679939844Sym1 n6989586621679948454 :: TyFun k Bool -> Type) (x6989586621679948455 :: k) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948456Scrutinee_6989586621679939844Sym1 n6989586621679948454 :: TyFun k Bool -> Type) (x6989586621679948455 :: k) = Let6989586621679948456Scrutinee_6989586621679939844 n6989586621679948454 x6989586621679948455
type Apply (Bool_Sym2 a6989586621679359157 a6989586621679359156 :: TyFun Bool a -> Type) (a6989586621679359158 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Bool

type Apply (Bool_Sym2 a6989586621679359157 a6989586621679359156 :: TyFun Bool a -> Type) (a6989586621679359158 :: Bool) = Bool_ a6989586621679359157 a6989586621679359156 a6989586621679359158
type Apply (Let6989586621679948443Scrutinee_6989586621679939846Sym2 xs6989586621679948441 x6989586621679948440 :: TyFun k3 Bool -> Type) (n6989586621679948442 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948443Scrutinee_6989586621679939846Sym2 xs6989586621679948441 x6989586621679948440 :: TyFun k3 Bool -> Type) (n6989586621679948442 :: k3) = Let6989586621679948443Scrutinee_6989586621679939846 xs6989586621679948441 x6989586621679948440 n6989586621679948442
type Apply (Let6989586621679948539Scrutinee_6989586621679939830Sym2 x6989586621679948537 n6989586621679948536 :: TyFun k3 Bool -> Type) (xs6989586621679948538 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948539Scrutinee_6989586621679939830Sym2 x6989586621679948537 n6989586621679948536 :: TyFun k3 Bool -> Type) (xs6989586621679948538 :: k3) = Let6989586621679948539Scrutinee_6989586621679939830 x6989586621679948537 n6989586621679948536 xs6989586621679948538
type Apply (Let6989586621679948553Scrutinee_6989586621679939828Sym2 x6989586621679948551 n6989586621679948550 :: TyFun k3 Bool -> Type) (xs6989586621679948552 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948553Scrutinee_6989586621679939828Sym2 x6989586621679948551 n6989586621679948550 :: TyFun k3 Bool -> Type) (xs6989586621679948552 :: k3) = Let6989586621679948553Scrutinee_6989586621679939828 x6989586621679948551 n6989586621679948550 xs6989586621679948552
type Apply (Lambda_6989586621680451077Sym2 t6989586621680451084 a_69895866216804510726989586621680451076 :: TyFun k3 Bool -> Type) (t6989586621680451085 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Lambda_6989586621680451077Sym2 t6989586621680451084 a_69895866216804510726989586621680451076 :: TyFun k3 Bool -> Type) (t6989586621680451085 :: k3) = Lambda_6989586621680451077 t6989586621680451084 a_69895866216804510726989586621680451076 t6989586621680451085
type Apply (Let6989586621679948524Scrutinee_6989586621679939840Sym3 y6989586621679948522 x6989586621679948521 key6989586621679948520 :: TyFun k3 Bool -> Type) (xys6989586621679948523 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948524Scrutinee_6989586621679939840Sym3 y6989586621679948522 x6989586621679948521 key6989586621679948520 :: TyFun k3 Bool -> Type) (xys6989586621679948523 :: k3) = Let6989586621679948524Scrutinee_6989586621679939840 y6989586621679948522 x6989586621679948521 key6989586621679948520 xys6989586621679948523
type Apply (Let6989586621679949754Scrutinee_6989586621679939822Sym3 xs6989586621679949753 x6989586621679949752 p6989586621679949748 :: TyFun k Bool -> Type) (a_69895866216799497466989586621679949749 :: k) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679949754Scrutinee_6989586621679939822Sym3 xs6989586621679949753 x6989586621679949752 p6989586621679949748 :: TyFun k Bool -> Type) (a_69895866216799497466989586621679949749 :: k) = Let6989586621679949754Scrutinee_6989586621679939822 xs6989586621679949753 x6989586621679949752 p6989586621679949748 a_69895866216799497466989586621679949749
type Apply (Let6989586621679739617Scrutinee_6989586621679739383Sym4 arg_69895866216797393796989586621679739603 x6989586621679739616 y6989586621679739608 x06989586621679739607 :: TyFun k4 Bool -> Type) (arg_69895866216797393816989586621679739604 :: k4) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621679739617Scrutinee_6989586621679739383Sym4 arg_69895866216797393796989586621679739603 x6989586621679739616 y6989586621679739608 x06989586621679739607 :: TyFun k4 Bool -> Type) (arg_69895866216797393816989586621679739604 :: k4) = Let6989586621679739617Scrutinee_6989586621679739383 arg_69895866216797393796989586621679739603 x6989586621679739616 y6989586621679739608 x06989586621679739607 arg_69895866216797393816989586621679739604
type Apply (Let6989586621679739483Scrutinee_6989586621679739407Sym5 arg_69895866216797394036989586621679739474 arg_69895866216797394016989586621679739473 y6989586621679739480 x26989586621679739479 x16989586621679739478 :: TyFun k5 Bool -> Type) (arg_69895866216797394056989586621679739475 :: k5) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621679739483Scrutinee_6989586621679739407Sym5 arg_69895866216797394036989586621679739474 arg_69895866216797394016989586621679739473 y6989586621679739480 x26989586621679739479 x16989586621679739478 :: TyFun k5 Bool -> Type) (arg_69895866216797394056989586621679739475 :: k5) = Let6989586621679739483Scrutinee_6989586621679739407 arg_69895866216797394036989586621679739474 arg_69895866216797394016989586621679739473 y6989586621679739480 x26989586621679739479 x16989586621679739478 arg_69895866216797394056989586621679739475
type Apply (Let6989586621679739540Scrutinee_6989586621679739397Sym5 arg_69895866216797393936989586621679739531 arg_69895866216797393916989586621679739530 y6989586621679739537 x26989586621679739536 x16989586621679739535 :: TyFun k5 Bool -> Type) (arg_69895866216797393956989586621679739532 :: k5) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621679739540Scrutinee_6989586621679739397Sym5 arg_69895866216797393936989586621679739531 arg_69895866216797393916989586621679739530 y6989586621679739537 x26989586621679739536 x16989586621679739535 :: TyFun k5 Bool -> Type) (arg_69895866216797393956989586621679739532 :: k5) = Let6989586621679739540Scrutinee_6989586621679739397 arg_69895866216797393936989586621679739531 arg_69895866216797393916989586621679739530 y6989586621679739537 x26989586621679739536 x16989586621679739535 arg_69895866216797393956989586621679739532
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 OrSym0 (a6989586621679949436 :: [Bool]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply OrSym0 (a6989586621679949436 :: [Bool]) = Or a6989586621679949436
type Apply AndSym0 (a6989586621679949440 :: [Bool]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply AndSym0 (a6989586621679949440 :: [Bool]) = And a6989586621679949440
type Apply (ListnullSym0 :: TyFun [a] Bool -> Type) (a6989586621680387653 :: [a]) 
Instance details

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

type Apply (ListnullSym0 :: TyFun [a] Bool -> Type) (a6989586621680387653 :: [a]) = Listnull a6989586621680387653
type Apply (NullSym0 :: TyFun [a] Bool -> Type) (a6989586621679949740 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (NullSym0 :: TyFun [a] Bool -> Type) (a6989586621679949740 :: [a]) = Null a6989586621679949740
type Apply (IsNothingSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679494823 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (IsNothingSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679494823 :: Maybe a) = IsNothing a6989586621679494823
type Apply (IsJustSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679494825 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (IsJustSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679494825 :: Maybe a) = IsJust a6989586621679494825
type Apply (AndSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680450687 :: t Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AndSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680450687 :: t Bool) = And a6989586621680450687
type Apply (OrSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680450678 :: t Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (OrSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680450678 :: t Bool) = Or a6989586621680450678
type Apply (Null_6989586621680675698Sym0 :: TyFun (Identity a) Bool -> Type) (a6989586621680675697 :: Identity a) 
Instance details

Defined in Data.Singletons.Prelude.Identity

type Apply (Null_6989586621680675698Sym0 :: TyFun (Identity a) Bool -> Type) (a6989586621680675697 :: Identity a) = Null_6989586621680675698 a6989586621680675697
type Apply (Let6989586621680450690Scrutinee_6989586621680450448Sym0 :: TyFun (t6989586621680450201 Bool) All -> Type) (x6989586621680450689 :: t6989586621680450201 Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680450690Scrutinee_6989586621680450448Sym0 :: TyFun (t6989586621680450201 Bool) All -> Type) (x6989586621680450689 :: t6989586621680450201 Bool) = Let6989586621680450690Scrutinee_6989586621680450448 x6989586621680450689
type Apply (Let6989586621680450681Scrutinee_6989586621680450450Sym0 :: TyFun (t6989586621680450201 Bool) Any -> Type) (x6989586621680450680 :: t6989586621680450201 Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680450681Scrutinee_6989586621680450450Sym0 :: TyFun (t6989586621680450201 Bool) Any -> Type) (x6989586621680450680 :: t6989586621680450201 Bool) = Let6989586621680450681Scrutinee_6989586621680450450 x6989586621680450680
type Apply (ListelemSym1 a6989586621680387735 :: TyFun [a] Bool -> Type) (a6989586621680387736 :: [a]) 
Instance details

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

type Apply (ListelemSym1 a6989586621680387735 :: TyFun [a] Bool -> Type) (a6989586621680387736 :: [a]) = Listelem a6989586621680387735 a6989586621680387736
type Apply (ListisPrefixOfSym1 a6989586621680387800 :: TyFun [a] Bool -> Type) (a6989586621680387801 :: [a]) 
Instance details

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

type Apply (ListisPrefixOfSym1 a6989586621680387800 :: TyFun [a] Bool -> Type) (a6989586621680387801 :: [a]) = ListisPrefixOf a6989586621680387800 a6989586621680387801
type Apply (NotElemSym1 a6989586621679949109 :: TyFun [a] Bool -> Type) (a6989586621679949110 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (NotElemSym1 a6989586621679949109 :: TyFun [a] Bool -> Type) (a6989586621679949110 :: [a]) = NotElem a6989586621679949109 a6989586621679949110
type Apply (ElemSym1 a6989586621679949116 :: TyFun [a] Bool -> Type) (a6989586621679949117 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ElemSym1 a6989586621679949116 :: TyFun [a] Bool -> Type) (a6989586621679949117 :: [a]) = Elem a6989586621679949116 a6989586621679949117
type Apply (IsPrefixOfSym1 a6989586621679949143 :: TyFun [a] Bool -> Type) (a6989586621679949144 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IsPrefixOfSym1 a6989586621679949143 :: TyFun [a] Bool -> Type) (a6989586621679949144 :: [a]) = IsPrefixOf a6989586621679949143 a6989586621679949144
type Apply (AnySym1 a6989586621679949374 :: TyFun [a] Bool -> Type) (a6989586621679949375 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (AnySym1 a6989586621679949374 :: TyFun [a] Bool -> Type) (a6989586621679949375 :: [a]) = Any a6989586621679949374 a6989586621679949375
type Apply (IsInfixOfSym1 a6989586621679949381 :: TyFun [a] Bool -> Type) (a6989586621679949382 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IsInfixOfSym1 a6989586621679949381 :: TyFun [a] Bool -> Type) (a6989586621679949382 :: [a]) = IsInfixOf a6989586621679949381 a6989586621679949382
type Apply (AllSym1 a6989586621679949429 :: TyFun [a] Bool -> Type) (a6989586621679949430 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (AllSym1 a6989586621679949429 :: TyFun [a] Bool -> Type) (a6989586621679949430 :: [a]) = All a6989586621679949429 a6989586621679949430
type Apply (IsSuffixOfSym1 a6989586621679949734 :: TyFun [a] Bool -> Type) (a6989586621679949735 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IsSuffixOfSym1 a6989586621679949734 :: TyFun [a] Bool -> Type) (a6989586621679949735 :: [a]) = IsSuffixOf a6989586621679949734 a6989586621679949735
type Apply (Elem_6989586621680675575Sym1 a6989586621680675573 :: TyFun (Identity a) Bool -> Type) (a6989586621680675574 :: Identity a) 
Instance details

Defined in Data.Singletons.Prelude.Identity

type Apply (Elem_6989586621680675575Sym1 a6989586621680675573 :: TyFun (Identity a) Bool -> Type) (a6989586621680675574 :: Identity a) = Elem_6989586621680675575 a6989586621680675573 a6989586621680675574
type Apply (Elem_bySym2 a6989586621679948402 a6989586621679948401 :: TyFun [a] Bool -> Type) (a6989586621679948403 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Elem_bySym2 a6989586621679948402 a6989586621679948401 :: TyFun [a] Bool -> Type) (a6989586621679948403 :: [a]) = Elem_by a6989586621679948402 a6989586621679948401 a6989586621679948403
type Apply (Elem_6989586621680451127Sym1 a6989586621680451125 t :: TyFun (t a) Bool -> Type) (a6989586621680451126 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680451127Sym1 a6989586621680451125 t :: TyFun (t a) Bool -> Type) (a6989586621680451126 :: t a) = Elem_6989586621680451127 a6989586621680451125 a6989586621680451126
type Apply (Null_6989586621680451090Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680451089 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Null_6989586621680451090Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680451089 :: t a) = Null_6989586621680451090 a6989586621680451089
type Apply (AnySym1 a6989586621680450665 t :: TyFun (t a) Bool -> Type) (a6989586621680450666 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AnySym1 a6989586621680450665 t :: TyFun (t a) Bool -> Type) (a6989586621680450666 :: t a) = Any a6989586621680450665 a6989586621680450666
type Apply (ElemSym1 arg6989586621680450868 t :: TyFun (t a) Bool -> Type) (arg6989586621680450869 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ElemSym1 arg6989586621680450868 t :: TyFun (t a) Bool -> Type) (arg6989586621680450869 :: t a) = Elem arg6989586621680450868 arg6989586621680450869
type Apply (NotElemSym1 a6989586621680450594 t :: TyFun (t a) Bool -> Type) (a6989586621680450595 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (NotElemSym1 a6989586621680450594 t :: TyFun (t a) Bool -> Type) (a6989586621680450595 :: t a) = NotElem a6989586621680450594 a6989586621680450595
type Apply (NullSym0 :: TyFun (t a) Bool -> Type) (arg6989586621680450864 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (NullSym0 :: TyFun (t a) Bool -> Type) (arg6989586621680450864 :: t a) = Null arg6989586621680450864
type Apply (AllSym1 a6989586621680450652 t :: TyFun (t a) Bool -> Type) (a6989586621680450653 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AllSym1 a6989586621680450652 t :: TyFun (t a) Bool -> Type) (a6989586621680450653 :: t a) = All a6989586621680450652 a6989586621680450653
type Apply (Elem_6989586621680451250Sym1 a6989586621680451248 t :: TyFun (t a) Bool -> Type) (a6989586621680451249 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680451250Sym1 a6989586621680451248 t :: TyFun (t a) Bool -> Type) (a6989586621680451249 :: t a) = Elem_6989586621680451250 a6989586621680451248 a6989586621680451249
type Apply (Null_6989586621680451388Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680451387 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Null_6989586621680451388Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680451387 :: t a) = Null_6989586621680451388 a6989586621680451387
type Apply (Null_6989586621680451564Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680451563 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Null_6989586621680451564Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680451563 :: t a) = Null_6989586621680451564 a6989586621680451563
type Apply (Elem_6989586621680451587Sym1 a6989586621680451585 t :: TyFun (t a) Bool -> Type) (a6989586621680451586 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680451587Sym1 a6989586621680451585 t :: TyFun (t a) Bool -> Type) (a6989586621680451586 :: t a) = Elem_6989586621680451587 a6989586621680451585 a6989586621680451586
type Apply (Null_6989586621680451710Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680451709 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Null_6989586621680451710Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680451709 :: t a) = Null_6989586621680451710 a6989586621680451709
type Apply (Elem_6989586621680451754Sym1 a6989586621680451752 t :: TyFun (t a) Bool -> Type) (a6989586621680451753 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680451754Sym1 a6989586621680451752 t :: TyFun (t a) Bool -> Type) (a6989586621680451753 :: t a) = Elem_6989586621680451754 a6989586621680451752 a6989586621680451753
type Apply (Null_6989586621680451877Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680451876 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Null_6989586621680451877Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680451876 :: t a) = Null_6989586621680451877 a6989586621680451876
type Apply (Elem_6989586621680451921Sym1 a6989586621680451919 t :: TyFun (t a) Bool -> Type) (a6989586621680451920 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680451921Sym1 a6989586621680451919 t :: TyFun (t a) Bool -> Type) (a6989586621680451920 :: t a) = Elem_6989586621680451921 a6989586621680451919 a6989586621680451920
type Apply (Null_6989586621680452044Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680452043 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Null_6989586621680452044Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680452043 :: t a) = Null_6989586621680452044 a6989586621680452043
type Apply (Let6989586621679949135Scrutinee_6989586621679939848Sym3 xs6989586621679949133 x6989586621679949132 l6989586621679949125 :: TyFun [k1] Bool -> Type) (ls6989586621679949134 :: [k1]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679949135Scrutinee_6989586621679939848Sym3 xs6989586621679949133 x6989586621679949132 l6989586621679949125 :: TyFun [k1] Bool -> Type) (ls6989586621679949134 :: [k1]) = Let6989586621679949135Scrutinee_6989586621679939848 xs6989586621679949133 x6989586621679949132 l6989586621679949125 ls6989586621679949134
type Apply (Let6989586621679948427Scrutinee_6989586621679939850Sym4 ys6989586621679948425 y6989586621679948424 l6989586621679948416 eq6989586621679948415 :: TyFun [k2] Bool -> Type) (xs6989586621679948426 :: [k2]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948427Scrutinee_6989586621679939850Sym4 ys6989586621679948425 y6989586621679948424 l6989586621679948416 eq6989586621679948415 :: TyFun [k2] Bool -> Type) (xs6989586621679948426 :: [k2]) = Let6989586621679948427Scrutinee_6989586621679939850 ys6989586621679948425 y6989586621679948424 l6989586621679948416 eq6989586621679948415 xs6989586621679948426
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 (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 (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 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 Apply (IsRightSym0 :: TyFun (Either a b) Bool -> Type) (a6989586621680432014 :: Either a b) 
Instance details

Defined in Data.Singletons.Prelude.Either

type Apply (IsRightSym0 :: TyFun (Either a b) Bool -> Type) (a6989586621680432014 :: Either a b) = IsRight a6989586621680432014
type Apply (IsLeftSym0 :: TyFun (Either a b) Bool -> Type) (a6989586621680432016 :: Either a b) 
Instance details

Defined in Data.Singletons.Prelude.Either

type Apply (IsLeftSym0 :: TyFun (Either a b) Bool -> Type) (a6989586621680432016 :: Either a b) = IsLeft a6989586621680432016
type Apply (TFHelper_6989586621680882327Sym1 a6989586621680882325 :: TyFun (Arg a b) Bool -> Type) (a6989586621680882326 :: Arg a b) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Apply (TFHelper_6989586621680882327Sym1 a6989586621680882325 :: TyFun (Arg a b) Bool -> Type) (a6989586621680882326 :: Arg a b) = TFHelper_6989586621680882327 a6989586621680882325 a6989586621680882326
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 (Guarded x ((p := y) ': ys) :: a2 -> Type) 
Instance details

Defined in Fcf.Data.Bool

type Eval (Guarded x ((p := y) ': ys) :: a2 -> Type) = Eval (If (Eval (p x)) y (Guarded x ys))
type Apply (GuardSym0 :: TyFun Bool (f6989586621679544065 ()) -> Type) (a6989586621679544234 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (GuardSym0 :: TyFun Bool (f6989586621679544065 ()) -> Type) (a6989586621679544234 :: Bool) = (Guard a6989586621679544234 :: f6989586621679544065 ())
type Arg (a -> Bool) 
Instance details

Defined in Test.Hspec.Core.Example

type Arg (a -> Bool) = a
type Apply (||@#@$) (a6989586621679360142 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Bool

type Apply (||@#@$) (a6989586621679360142 :: Bool) = (||@#@$$) a6989586621679360142
type Apply (&&@#@$) (a6989586621679359901 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Bool

type Apply (&&@#@$) (a6989586621679359901 :: Bool) = (&&@#@$$) a6989586621679359901
type Apply Compare_6989586621679390848Sym0 (a6989586621679390846 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply Compare_6989586621679390848Sym0 (a6989586621679390846 :: Bool) = Compare_6989586621679390848Sym1 a6989586621679390846
type Apply ShowsPrec_6989586621680280441Sym0 (a6989586621680280438 :: Nat) 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply ShowsPrec_6989586621680280441Sym0 (a6989586621680280438 :: Nat) = ShowsPrec_6989586621680280441Sym1 a6989586621680280438
type Apply (<=?@#@$) (a3530822107858468865 :: Nat) 
Instance details

Defined in Data.Singletons.TypeLits.Internal

type Apply (<=?@#@$) (a3530822107858468865 :: Nat) = (<=?@#@$$) a3530822107858468865
type Apply ShowParenSym0 (a6989586621680262099 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply ShowParenSym0 (a6989586621680262099 :: Bool) = ShowParenSym1 a6989586621680262099
type Apply (Let6989586621680441997Scrutinee_6989586621680441960Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621680441990 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680441997Scrutinee_6989586621680441960Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621680441990 :: k1) = Let6989586621680441997Scrutinee_6989586621680441960Sym1 x6989586621680441990
type Apply (Let6989586621680442024Scrutinee_6989586621680441962Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621680442017 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680442024Scrutinee_6989586621680441962Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621680442017 :: k1) = Let6989586621680442024Scrutinee_6989586621680441962Sym1 x6989586621680442017
type Apply (Let6989586621679379574Scrutinee_6989586621679379469Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679379572 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Let6989586621679379574Scrutinee_6989586621679379469Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679379572 :: k1) = Let6989586621679379574Scrutinee_6989586621679379469Sym1 x6989586621679379572
type Apply (Let6989586621679379688Scrutinee_6989586621679379483Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679379686 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Let6989586621679379688Scrutinee_6989586621679379483Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679379686 :: k1) = Let6989586621679379688Scrutinee_6989586621679379483Sym1 x6989586621679379686
type Apply (Let6989586621679379670Scrutinee_6989586621679379481Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679379668 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Let6989586621679379670Scrutinee_6989586621679379481Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679379668 :: k1) = Let6989586621679379670Scrutinee_6989586621679379481Sym1 x6989586621679379668
type Apply (Let6989586621679379579Scrutinee_6989586621679379471Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679379572 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Let6989586621679379579Scrutinee_6989586621679379471Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679379572 :: k1) = Let6989586621679379579Scrutinee_6989586621679379471Sym1 x6989586621679379572
type Apply (ListelemSym0 :: TyFun a6989586621680386736 ([a6989586621680386736] ~> Bool) -> Type) (a6989586621680387735 :: a6989586621680386736) 
Instance details

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

type Apply (ListelemSym0 :: TyFun a6989586621680386736 ([a6989586621680386736] ~> Bool) -> Type) (a6989586621680387735 :: a6989586621680386736) = ListelemSym1 a6989586621680387735
type Apply (NotElemSym0 :: TyFun a6989586621679939225 ([a6989586621679939225] ~> Bool) -> Type) (a6989586621679949109 :: a6989586621679939225) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (NotElemSym0 :: TyFun a6989586621679939225 ([a6989586621679939225] ~> Bool) -> Type) (a6989586621679949109 :: a6989586621679939225) = NotElemSym1 a6989586621679949109
type Apply (ElemSym0 :: TyFun a6989586621679939226 ([a6989586621679939226] ~> Bool) -> Type) (a6989586621679949116 :: a6989586621679939226) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ElemSym0 :: TyFun a6989586621679939226 ([a6989586621679939226] ~> Bool) -> Type) (a6989586621679949116 :: a6989586621679939226) = ElemSym1 a6989586621679949116
type Apply (ShowsPrec_6989586621680280441Sym1 a6989586621680280438 :: TyFun Bool (Symbol ~> Symbol) -> Type) (a6989586621680280439 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowsPrec_6989586621680280441Sym1 a6989586621680280438 :: TyFun Bool (Symbol ~> Symbol) -> Type) (a6989586621680280439 :: Bool) = ShowsPrec_6989586621680280441Sym2 a6989586621680280438 a6989586621680280439
type Apply (WhenSym0 :: TyFun Bool (f6989586621679544094 () ~> f6989586621679544094 ()) -> Type) (a6989586621679544482 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (WhenSym0 :: TyFun Bool (f6989586621679544094 () ~> f6989586621679544094 ()) -> Type) (a6989586621679544482 :: Bool) = (WhenSym1 a6989586621679544482 f6989586621679544094 :: TyFun (f6989586621679544094 ()) (f6989586621679544094 ()) -> Type)
type Apply ((==@#@$) :: TyFun a6989586621679363170 (a6989586621679363170 ~> Bool) -> Type) (x6989586621679363171 :: a6989586621679363170) 
Instance details

Defined in Data.Singletons.Prelude.Eq

type Apply ((==@#@$) :: TyFun a6989586621679363170 (a6989586621679363170 ~> Bool) -> Type) (x6989586621679363171 :: a6989586621679363170) = (==@#@$$) x6989586621679363171
type Apply ((/=@#@$) :: TyFun a6989586621679363170 (a6989586621679363170 ~> Bool) -> Type) (x6989586621679363173 :: a6989586621679363170) 
Instance details

Defined in Data.Singletons.Prelude.Eq

type Apply ((/=@#@$) :: TyFun a6989586621679363170 (a6989586621679363170 ~> Bool) -> Type) (x6989586621679363173 :: a6989586621679363170) = (/=@#@$$) x6989586621679363173
type Apply (DefaultEqSym0 :: TyFun k6989586621679363164 (k6989586621679363164 ~> Bool) -> Type) (a6989586621679363165 :: k6989586621679363164) 
Instance details

Defined in Data.Singletons.Prelude.Eq

type Apply (DefaultEqSym0 :: TyFun k6989586621679363164 (k6989586621679363164 ~> Bool) -> Type) (a6989586621679363165 :: k6989586621679363164) = DefaultEqSym1 a6989586621679363165
type Apply (Bool_Sym0 :: TyFun a6989586621679359150 (a6989586621679359150 ~> (Bool ~> a6989586621679359150)) -> Type) (a6989586621679359156 :: a6989586621679359150) 
Instance details

Defined in Data.Singletons.Prelude.Bool

type Apply (Bool_Sym0 :: TyFun a6989586621679359150 (a6989586621679359150 ~> (Bool ~> a6989586621679359150)) -> Type) (a6989586621679359156 :: a6989586621679359150) = Bool_Sym1 a6989586621679359156
type Apply (TFHelper_6989586621679379660Sym0 :: TyFun a6989586621679379451 (a6989586621679379451 ~> Bool) -> Type) (a6989586621679379658 :: a6989586621679379451) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (TFHelper_6989586621679379660Sym0 :: TyFun a6989586621679379451 (a6989586621679379451 ~> Bool) -> Type) (a6989586621679379658 :: a6989586621679379451) = TFHelper_6989586621679379660Sym1 a6989586621679379658
type Apply (TFHelper_6989586621679379642Sym0 :: TyFun a6989586621679379451 (a6989586621679379451 ~> Bool) -> Type) (a6989586621679379640 :: a6989586621679379451) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (TFHelper_6989586621679379642Sym0 :: TyFun a6989586621679379451 (a6989586621679379451 ~> Bool) -> Type) (a6989586621679379640 :: a6989586621679379451) = TFHelper_6989586621679379642Sym1 a6989586621679379640
type Apply (TFHelper_6989586621679379624Sym0 :: TyFun a6989586621679379451 (a6989586621679379451 ~> Bool) -> Type) (a6989586621679379622 :: a6989586621679379451) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (TFHelper_6989586621679379624Sym0 :: TyFun a6989586621679379451 (a6989586621679379451 ~> Bool) -> Type) (a6989586621679379622 :: a6989586621679379451) = TFHelper_6989586621679379624Sym1 a6989586621679379622
type Apply (TFHelper_6989586621679379606Sym0 :: TyFun a6989586621679379451 (a6989586621679379451 ~> Bool) -> Type) (a6989586621679379604 :: a6989586621679379451) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (TFHelper_6989586621679379606Sym0 :: TyFun a6989586621679379451 (a6989586621679379451 ~> Bool) -> Type) (a6989586621679379604 :: a6989586621679379451) = TFHelper_6989586621679379606Sym1 a6989586621679379604
type Apply ((<=@#@$) :: TyFun a6989586621679379451 (a6989586621679379451 ~> Bool) -> Type) (arg6989586621679379548 :: a6989586621679379451) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply ((<=@#@$) :: TyFun a6989586621679379451 (a6989586621679379451 ~> Bool) -> Type) (arg6989586621679379548 :: a6989586621679379451) = (<=@#@$$) arg6989586621679379548
type Apply ((>=@#@$) :: TyFun a6989586621679379451 (a6989586621679379451 ~> Bool) -> Type) (arg6989586621679379556 :: a6989586621679379451) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply ((>=@#@$) :: TyFun a6989586621679379451 (a6989586621679379451 ~> Bool) -> Type) (arg6989586621679379556 :: a6989586621679379451) = (>=@#@$$) arg6989586621679379556
type Apply ((>@#@$) :: TyFun a6989586621679379451 (a6989586621679379451 ~> Bool) -> Type) (arg6989586621679379552 :: a6989586621679379451) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply ((>@#@$) :: TyFun a6989586621679379451 (a6989586621679379451 ~> Bool) -> Type) (arg6989586621679379552 :: a6989586621679379451) = (>@#@$$) arg6989586621679379552
type Apply ((<@#@$) :: TyFun a6989586621679379451 (a6989586621679379451 ~> Bool) -> Type) (arg6989586621679379544 :: a6989586621679379451) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply ((<@#@$) :: TyFun a6989586621679379451 (a6989586621679379451 ~> Bool) -> Type) (arg6989586621679379544 :: a6989586621679379451) = (<@#@$$) arg6989586621679379544
type Apply (Elem_6989586621680675575Sym0 :: TyFun a6989586621680450218 (Identity a6989586621680450218 ~> Bool) -> Type) (a6989586621680675573 :: a6989586621680450218) 
Instance details

Defined in Data.Singletons.Prelude.Identity

type Apply (Elem_6989586621680675575Sym0 :: TyFun a6989586621680450218 (Identity a6989586621680450218 ~> Bool) -> Type) (a6989586621680675573 :: a6989586621680450218) = Elem_6989586621680675575Sym1 a6989586621680675573
type Apply (Let6989586621679948456Scrutinee_6989586621679939844Sym0 :: TyFun k1 (TyFun k Bool -> Type) -> Type) (n6989586621679948454 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948456Scrutinee_6989586621679939844Sym0 :: TyFun k1 (TyFun k Bool -> Type) -> Type) (n6989586621679948454 :: k1) = (Let6989586621679948456Scrutinee_6989586621679939844Sym1 n6989586621679948454 :: TyFun k Bool -> Type)
type Apply (Bool_Sym1 a6989586621679359156 :: TyFun a6989586621679359150 (Bool ~> a6989586621679359150) -> Type) (a6989586621679359157 :: a6989586621679359150) 
Instance details

Defined in Data.Singletons.Prelude.Bool

type Apply (Bool_Sym1 a6989586621679359156 :: TyFun a6989586621679359150 (Bool ~> a6989586621679359150) -> Type) (a6989586621679359157 :: a6989586621679359150) = Bool_Sym2 a6989586621679359156 a6989586621679359157
type Apply (Elem_bySym1 a6989586621679948401 :: TyFun a6989586621679939143 ([a6989586621679939143] ~> Bool) -> Type) (a6989586621679948402 :: a6989586621679939143) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Elem_bySym1 a6989586621679948401 :: TyFun a6989586621679939143 ([a6989586621679939143] ~> Bool) -> Type) (a6989586621679948402 :: a6989586621679939143) = Elem_bySym2 a6989586621679948401 a6989586621679948402
type Apply (Elem_6989586621680451127Sym0 :: TyFun a6989586621680450218 (t6989586621680450201 a6989586621680450218 ~> Bool) -> Type) (a6989586621680451125 :: a6989586621680450218) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680451127Sym0 :: TyFun a6989586621680450218 (t6989586621680450201 a6989586621680450218 ~> Bool) -> Type) (a6989586621680451125 :: a6989586621680450218) = (Elem_6989586621680451127Sym1 a6989586621680451125 t6989586621680450201 :: TyFun (t6989586621680450201 a6989586621680450218) Bool -> Type)
type Apply (ElemSym0 :: TyFun a6989586621680450218 (t6989586621680450201 a6989586621680450218 ~> Bool) -> Type) (arg6989586621680450868 :: a6989586621680450218) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ElemSym0 :: TyFun a6989586621680450218 (t6989586621680450201 a6989586621680450218 ~> Bool) -> Type) (arg6989586621680450868 :: a6989586621680450218) = (ElemSym1 arg6989586621680450868 t6989586621680450201 :: TyFun (t6989586621680450201 a6989586621680450218) Bool -> Type)
type Apply (NotElemSym0 :: TyFun a6989586621680450112 (t6989586621680450111 a6989586621680450112 ~> Bool) -> Type) (a6989586621680450594 :: a6989586621680450112) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (NotElemSym0 :: TyFun a6989586621680450112 (t6989586621680450111 a6989586621680450112 ~> Bool) -> Type) (a6989586621680450594 :: a6989586621680450112) = (NotElemSym1 a6989586621680450594 t6989586621680450111 :: TyFun (t6989586621680450111 a6989586621680450112) Bool -> Type)
type Apply (Elem_6989586621680451250Sym0 :: TyFun a6989586621680450218 (t6989586621680450201 a6989586621680450218 ~> Bool) -> Type) (a6989586621680451248 :: a6989586621680450218) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680451250Sym0 :: TyFun a6989586621680450218 (t6989586621680450201 a6989586621680450218 ~> Bool) -> Type) (a6989586621680451248 :: a6989586621680450218) = (Elem_6989586621680451250Sym1 a6989586621680451248 t6989586621680450201 :: TyFun (t6989586621680450201 a6989586621680450218) Bool -> Type)
type Apply (Elem_6989586621680451587Sym0 :: TyFun a6989586621680450218 (t6989586621680450201 a6989586621680450218 ~> Bool) -> Type) (a6989586621680451585 :: a6989586621680450218) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680451587Sym0 :: TyFun a6989586621680450218 (t6989586621680450201 a6989586621680450218 ~> Bool) -> Type) (a6989586621680451585 :: a6989586621680450218) = (Elem_6989586621680451587Sym1 a6989586621680451585 t6989586621680450201 :: TyFun (t6989586621680450201 a6989586621680450218) Bool -> Type)
type Apply (Elem_6989586621680451754Sym0 :: TyFun a6989586621680450218 (t6989586621680450201 a6989586621680450218 ~> Bool) -> Type) (a6989586621680451752 :: a6989586621680450218) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680451754Sym0 :: TyFun a6989586621680450218 (t6989586621680450201 a6989586621680450218 ~> Bool) -> Type) (a6989586621680451752 :: a6989586621680450218) = (Elem_6989586621680451754Sym1 a6989586621680451752 t6989586621680450201 :: TyFun (t6989586621680450201 a6989586621680450218) Bool -> Type)
type Apply (Elem_6989586621680451921Sym0 :: TyFun a6989586621680450218 (t6989586621680450201 a6989586621680450218 ~> Bool) -> Type) (a6989586621680451919 :: a6989586621680450218) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680451921Sym0 :: TyFun a6989586621680450218 (t6989586621680450201 a6989586621680450218 ~> Bool) -> Type) (a6989586621680451919 :: a6989586621680450218) = (Elem_6989586621680451921Sym1 a6989586621680451919 t6989586621680450201 :: TyFun (t6989586621680450201 a6989586621680450218) Bool -> Type)
type Apply (Let6989586621679948443Scrutinee_6989586621679939846Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (x6989586621679948440 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948443Scrutinee_6989586621679939846Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (x6989586621679948440 :: k1) = (Let6989586621679948443Scrutinee_6989586621679939846Sym1 x6989586621679948440 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type)
type Apply (Let6989586621679948524Scrutinee_6989586621679939840Sym0 :: TyFun k1 (TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) (key6989586621679948520 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948524Scrutinee_6989586621679939840Sym0 :: TyFun k1 (TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) (key6989586621679948520 :: k1) = (Let6989586621679948524Scrutinee_6989586621679939840Sym1 key6989586621679948520 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type)
type Apply (Let6989586621679948539Scrutinee_6989586621679939830Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (n6989586621679948536 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948539Scrutinee_6989586621679939830Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (n6989586621679948536 :: k1) = (Let6989586621679948539Scrutinee_6989586621679939830Sym1 n6989586621679948536 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type)
type Apply (Let6989586621679948553Scrutinee_6989586621679939828Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (n6989586621679948550 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948553Scrutinee_6989586621679939828Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (n6989586621679948550 :: k1) = (Let6989586621679948553Scrutinee_6989586621679939828Sym1 n6989586621679948550 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type)
type Apply (Let6989586621679949135Scrutinee_6989586621679939848Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun [k2] Bool -> Type) -> Type) -> Type) -> Type) (l6989586621679949125 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679949135Scrutinee_6989586621679939848Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun [k2] Bool -> Type) -> Type) -> Type) -> Type) (l6989586621679949125 :: k1) = (Let6989586621679949135Scrutinee_6989586621679939848Sym1 l6989586621679949125 :: TyFun k2 (TyFun k3 (TyFun [k2] Bool -> Type) -> Type) -> Type)
type Apply (Lambda_6989586621680451077Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (a_69895866216804510726989586621680451076 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Lambda_6989586621680451077Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (a_69895866216804510726989586621680451076 :: k1) = (Lambda_6989586621680451077Sym1 a_69895866216804510726989586621680451076 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type)
type Apply (Let6989586621679949754Scrutinee_6989586621679939822Sym1 p6989586621679949748 :: TyFun k1 (TyFun [a6989586621679939263] (TyFun k Bool -> Type) -> Type) -> Type) (x6989586621679949752 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679949754Scrutinee_6989586621679939822Sym1 p6989586621679949748 :: TyFun k1 (TyFun [a6989586621679939263] (TyFun k Bool -> Type) -> Type) -> Type) (x6989586621679949752 :: k1) = (Let6989586621679949754Scrutinee_6989586621679939822Sym2 p6989586621679949748 x6989586621679949752 :: TyFun [a6989586621679939263] (TyFun k Bool -> Type) -> Type)
type Apply (Let6989586621679948443Scrutinee_6989586621679939846Sym1 x6989586621679948440 :: TyFun k1 (TyFun k3 Bool -> Type) -> Type) (xs6989586621679948441 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948443Scrutinee_6989586621679939846Sym1 x6989586621679948440 :: TyFun k1 (TyFun k3 Bool -> Type) -> Type) (xs6989586621679948441 :: k1) = (Let6989586621679948443Scrutinee_6989586621679939846Sym2 x6989586621679948440 xs6989586621679948441 :: TyFun k3 Bool -> Type)
type Apply (Let6989586621679948524Scrutinee_6989586621679939840Sym1 key6989586621679948520 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (x6989586621679948521 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948524Scrutinee_6989586621679939840Sym1 key6989586621679948520 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (x6989586621679948521 :: k1) = (Let6989586621679948524Scrutinee_6989586621679939840Sym2 key6989586621679948520 x6989586621679948521 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type)
type Apply (Let6989586621679948539Scrutinee_6989586621679939830Sym1 n6989586621679948536 :: TyFun k1 (TyFun k3 Bool -> Type) -> Type) (x6989586621679948537 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948539Scrutinee_6989586621679939830Sym1 n6989586621679948536 :: TyFun k1 (TyFun k3 Bool -> Type) -> Type) (x6989586621679948537 :: k1) = (Let6989586621679948539Scrutinee_6989586621679939830Sym2 n6989586621679948536 x6989586621679948537 :: TyFun k3 Bool -> Type)
type Apply (Let6989586621679948553Scrutinee_6989586621679939828Sym1 n6989586621679948550 :: TyFun k1 (TyFun k3 Bool -> Type) -> Type) (x6989586621679948551 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948553Scrutinee_6989586621679939828Sym1 n6989586621679948550 :: TyFun k1 (TyFun k3 Bool -> Type) -> Type) (x6989586621679948551 :: k1) = (Let6989586621679948553Scrutinee_6989586621679939828Sym2 n6989586621679948550 x6989586621679948551 :: TyFun k3 Bool -> Type)
type Apply (Let6989586621679948427Scrutinee_6989586621679939850Sym1 eq6989586621679948415 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun [k2] Bool -> Type) -> Type) -> Type) -> Type) (l6989586621679948416 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948427Scrutinee_6989586621679939850Sym1 eq6989586621679948415 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun [k2] Bool -> Type) -> Type) -> Type) -> Type) (l6989586621679948416 :: k1) = (Let6989586621679948427Scrutinee_6989586621679939850Sym2 eq6989586621679948415 l6989586621679948416 :: TyFun k2 (TyFun k3 (TyFun [k2] Bool -> Type) -> Type) -> Type)
type Apply (Let6989586621679949135Scrutinee_6989586621679939848Sym1 l6989586621679949125 :: TyFun k1 (TyFun k3 (TyFun [k1] Bool -> Type) -> Type) -> Type) (x6989586621679949132 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679949135Scrutinee_6989586621679939848Sym1 l6989586621679949125 :: TyFun k1 (TyFun k3 (TyFun [k1] Bool -> Type) -> Type) -> Type) (x6989586621679949132 :: k1) = (Let6989586621679949135Scrutinee_6989586621679939848Sym2 l6989586621679949125 x6989586621679949132 :: TyFun k3 (TyFun [k1] Bool -> Type) -> Type)
type Apply (Lambda_6989586621680451077Sym1 a_69895866216804510726989586621680451076 :: TyFun k1 (TyFun k3 Bool -> Type) -> Type) (t6989586621680451084 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Lambda_6989586621680451077Sym1 a_69895866216804510726989586621680451076 :: TyFun k1 (TyFun k3 Bool -> Type) -> Type) (t6989586621680451084 :: k1) = (Lambda_6989586621680451077Sym2 a_69895866216804510726989586621680451076 t6989586621680451084 :: TyFun k3 Bool -> Type)
type Apply (Let6989586621679739617Scrutinee_6989586621679739383Sym0 :: TyFun k1 (TyFun k2 (TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (x06989586621679739607 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621679739617Scrutinee_6989586621679739383Sym0 :: TyFun k1 (TyFun k2 (TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (x06989586621679739607 :: k1) = (Let6989586621679739617Scrutinee_6989586621679739383Sym1 x06989586621679739607 :: TyFun k2 (TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type)
type Apply (Let6989586621679949135Scrutinee_6989586621679939848Sym2 x6989586621679949132 l6989586621679949125 :: TyFun k3 (TyFun [k1] Bool -> Type) -> Type) (xs6989586621679949133 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679949135Scrutinee_6989586621679939848Sym2 x6989586621679949132 l6989586621679949125 :: TyFun k3 (TyFun [k1] Bool -> Type) -> Type) (xs6989586621679949133 :: k3) = Let6989586621679949135Scrutinee_6989586621679939848Sym3 x6989586621679949132 l6989586621679949125 xs6989586621679949133
type Apply (Let6989586621679948524Scrutinee_6989586621679939840Sym2 x6989586621679948521 key6989586621679948520 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) (y6989586621679948522 :: k2) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948524Scrutinee_6989586621679939840Sym2 x6989586621679948521 key6989586621679948520 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) (y6989586621679948522 :: k2) = (Let6989586621679948524Scrutinee_6989586621679939840Sym3 x6989586621679948521 key6989586621679948520 y6989586621679948522 :: TyFun k3 Bool -> Type)
type Apply (Let6989586621679948427Scrutinee_6989586621679939850Sym2 l6989586621679948416 eq6989586621679948415 :: TyFun k2 (TyFun k3 (TyFun [k2] Bool -> Type) -> Type) -> Type) (y6989586621679948424 :: k2) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948427Scrutinee_6989586621679939850Sym2 l6989586621679948416 eq6989586621679948415 :: TyFun k2 (TyFun k3 (TyFun [k2] Bool -> Type) -> Type) -> Type) (y6989586621679948424 :: k2) = (Let6989586621679948427Scrutinee_6989586621679939850Sym3 l6989586621679948416 eq6989586621679948415 y6989586621679948424 :: TyFun k3 (TyFun [k2] Bool -> Type) -> Type)
type Apply (Let6989586621679739483Scrutinee_6989586621679739407Sym0 :: TyFun k1 (TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (x16989586621679739478 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621679739483Scrutinee_6989586621679739407Sym0 :: TyFun k1 (TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (x16989586621679739478 :: k1) = (Let6989586621679739483Scrutinee_6989586621679739407Sym1 x16989586621679739478 :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type)
type Apply (Let6989586621679739540Scrutinee_6989586621679739397Sym0 :: TyFun k1 (TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (x16989586621679739535 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621679739540Scrutinee_6989586621679739397Sym0 :: TyFun k1 (TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (x16989586621679739535 :: k1) = (Let6989586621679739540Scrutinee_6989586621679739397Sym1 x16989586621679739535 :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type)
type Apply (Let6989586621679739617Scrutinee_6989586621679739383Sym1 x06989586621679739607 :: TyFun k1 (TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) (y6989586621679739608 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621679739617Scrutinee_6989586621679739383Sym1 x06989586621679739607 :: TyFun k1 (TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) (y6989586621679739608 :: k1) = (Let6989586621679739617Scrutinee_6989586621679739383Sym2 x06989586621679739607 y6989586621679739608 :: TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type)
type Apply (Let6989586621679948427Scrutinee_6989586621679939850Sym3 y6989586621679948424 l6989586621679948416 eq6989586621679948415 :: TyFun k3 (TyFun [k2] Bool -> Type) -> Type) (ys6989586621679948425 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948427Scrutinee_6989586621679939850Sym3 y6989586621679948424 l6989586621679948416 eq6989586621679948415 :: TyFun k3 (TyFun [k2] Bool -> Type) -> Type) (ys6989586621679948425 :: k3) = Let6989586621679948427Scrutinee_6989586621679939850Sym4 y6989586621679948424 l6989586621679948416 eq6989586621679948415 ys6989586621679948425
type Apply (Let6989586621679739483Scrutinee_6989586621679739407Sym1 x16989586621679739478 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (x26989586621679739479 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621679739483Scrutinee_6989586621679739407Sym1 x16989586621679739478 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (x26989586621679739479 :: k1) = (Let6989586621679739483Scrutinee_6989586621679739407Sym2 x16989586621679739478 x26989586621679739479 :: TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type)
type Apply (Let6989586621679739540Scrutinee_6989586621679739397Sym1 x16989586621679739535 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (x26989586621679739536 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621679739540Scrutinee_6989586621679739397Sym1 x16989586621679739535 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (x26989586621679739536 :: k1) = (Let6989586621679739540Scrutinee_6989586621679739397Sym2 x16989586621679739535 x26989586621679739536 :: TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type)
type Apply (Let6989586621679739617Scrutinee_6989586621679739383Sym2 y6989586621679739608 x06989586621679739607 :: TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) (x6989586621679739616 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621679739617Scrutinee_6989586621679739383Sym2 y6989586621679739608 x06989586621679739607 :: TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) (x6989586621679739616 :: k1) = (Let6989586621679739617Scrutinee_6989586621679739383Sym3 y6989586621679739608 x06989586621679739607 x6989586621679739616 :: TyFun k3 (TyFun k4 Bool -> Type) -> Type)
type Apply (Let6989586621679739483Scrutinee_6989586621679739407Sym2 x26989586621679739479 x16989586621679739478 :: TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) (y6989586621679739480 :: k2) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621679739483Scrutinee_6989586621679739407Sym2 x26989586621679739479 x16989586621679739478 :: TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) (y6989586621679739480 :: k2) = (Let6989586621679739483Scrutinee_6989586621679739407Sym3 x26989586621679739479 x16989586621679739478 y6989586621679739480 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type)
type Apply (Let6989586621679739540Scrutinee_6989586621679739397Sym2 x26989586621679739536 x16989586621679739535 :: TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) (y6989586621679739537 :: k2) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621679739540Scrutinee_6989586621679739397Sym2 x26989586621679739536 x16989586621679739535 :: TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) (y6989586621679739537 :: k2) = (Let6989586621679739540Scrutinee_6989586621679739397Sym3 x26989586621679739536 x16989586621679739535 y6989586621679739537 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type)
type Apply (Let6989586621679739617Scrutinee_6989586621679739383Sym3 x6989586621679739616 y6989586621679739608 x06989586621679739607 :: TyFun k3 (TyFun k4 Bool -> Type) -> Type) (arg_69895866216797393796989586621679739603 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621679739617Scrutinee_6989586621679739383Sym3 x6989586621679739616 y6989586621679739608 x06989586621679739607 :: TyFun k3 (TyFun k4 Bool -> Type) -> Type) (arg_69895866216797393796989586621679739603 :: k3) = (Let6989586621679739617Scrutinee_6989586621679739383Sym4 x6989586621679739616 y6989586621679739608 x06989586621679739607 arg_69895866216797393796989586621679739603 :: TyFun k4 Bool -> Type)
type Apply (Let6989586621679739483Scrutinee_6989586621679739407Sym3 y6989586621679739480 x26989586621679739479 x16989586621679739478 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) (arg_69895866216797394016989586621679739473 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621679739483Scrutinee_6989586621679739407Sym3 y6989586621679739480 x26989586621679739479 x16989586621679739478 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) (arg_69895866216797394016989586621679739473 :: k3) = (Let6989586621679739483Scrutinee_6989586621679739407Sym4 y6989586621679739480 x26989586621679739479 x16989586621679739478 arg_69895866216797394016989586621679739473 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type)
type Apply (Let6989586621679739540Scrutinee_6989586621679739397Sym3 y6989586621679739537 x26989586621679739536 x16989586621679739535 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) (arg_69895866216797393916989586621679739530 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621679739540Scrutinee_6989586621679739397Sym3 y6989586621679739537 x26989586621679739536 x16989586621679739535 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) (arg_69895866216797393916989586621679739530 :: k3) = (Let6989586621679739540Scrutinee_6989586621679739397Sym4 y6989586621679739537 x26989586621679739536 x16989586621679739535 arg_69895866216797393916989586621679739530 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type)
type Apply (Let6989586621679739483Scrutinee_6989586621679739407Sym4 arg_69895866216797394016989586621679739473 y6989586621679739480 x26989586621679739479 x16989586621679739478 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type) (arg_69895866216797394036989586621679739474 :: k4) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621679739483Scrutinee_6989586621679739407Sym4 arg_69895866216797394016989586621679739473 y6989586621679739480 x26989586621679739479 x16989586621679739478 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type) (arg_69895866216797394036989586621679739474 :: k4) = (Let6989586621679739483Scrutinee_6989586621679739407Sym5 arg_69895866216797394016989586621679739473 y6989586621679739480 x26989586621679739479 x16989586621679739478 arg_69895866216797394036989586621679739474 :: TyFun k5 Bool -> Type)
type Apply (Let6989586621679739540Scrutinee_6989586621679739397Sym4 arg_69895866216797393916989586621679739530 y6989586621679739537 x26989586621679739536 x16989586621679739535 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type) (arg_69895866216797393936989586621679739531 :: k4) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621679739540Scrutinee_6989586621679739397Sym4 arg_69895866216797393916989586621679739530 y6989586621679739537 x26989586621679739536 x16989586621679739535 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type) (arg_69895866216797393936989586621679739531 :: k4) = (Let6989586621679739540Scrutinee_6989586621679739397Sym5 arg_69895866216797393916989586621679739530 y6989586621679739537 x26989586621679739536 x16989586621679739535 arg_69895866216797393936989586621679739531 :: TyFun k5 Bool -> Type)
type Apply (ListisPrefixOfSym0 :: TyFun [a6989586621680386748] ([a6989586621680386748] ~> Bool) -> Type) (a6989586621680387800 :: [a6989586621680386748]) 
Instance details

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

type Apply (ListisPrefixOfSym0 :: TyFun [a6989586621680386748] ([a6989586621680386748] ~> Bool) -> Type) (a6989586621680387800 :: [a6989586621680386748]) = ListisPrefixOfSym1 a6989586621680387800
type Apply (IsPrefixOfSym0 :: TyFun [a6989586621679939229] ([a6989586621679939229] ~> Bool) -> Type) (a6989586621679949143 :: [a6989586621679939229]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IsPrefixOfSym0 :: TyFun [a6989586621679939229] ([a6989586621679939229] ~> Bool) -> Type) (a6989586621679949143 :: [a6989586621679939229]) = IsPrefixOfSym1 a6989586621679949143
type Apply (IsInfixOfSym0 :: TyFun [a6989586621679939227] ([a6989586621679939227] ~> Bool) -> Type) (a6989586621679949381 :: [a6989586621679939227]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IsInfixOfSym0 :: TyFun [a6989586621679939227] ([a6989586621679939227] ~> Bool) -> Type) (a6989586621679949381 :: [a6989586621679939227]) = IsInfixOfSym1 a6989586621679949381
type Apply (IsSuffixOfSym0 :: TyFun [a6989586621679939228] ([a6989586621679939228] ~> Bool) -> Type) (a6989586621679949734 :: [a6989586621679939228]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IsSuffixOfSym0 :: TyFun [a6989586621679939228] ([a6989586621679939228] ~> Bool) -> Type) (a6989586621679949734 :: [a6989586621679939228]) = IsSuffixOfSym1 a6989586621679949734
type Apply (Let6989586621679949754Scrutinee_6989586621679939822Sym2 x6989586621679949752 p6989586621679949748 :: TyFun [a6989586621679939263] (TyFun k Bool -> Type) -> Type) (xs6989586621679949753 :: [a6989586621679939263]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679949754Scrutinee_6989586621679939822Sym2 x6989586621679949752 p6989586621679949748 :: TyFun [a6989586621679939263] (TyFun k Bool -> Type) -> Type) (xs6989586621679949753 :: [a6989586621679939263]) = (Let6989586621679949754Scrutinee_6989586621679939822Sym3 x6989586621679949752 p6989586621679949748 xs6989586621679949753 :: TyFun k Bool -> Type)
type Apply (Let6989586621679948584ZsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621679948571 :: k ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948584ZsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621679948571 :: k ~> Bool) = Let6989586621679948584ZsSym1 p6989586621679948571
type Apply (Let6989586621679948584YsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621679948571 :: k ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948584YsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621679948571 :: k ~> Bool) = Let6989586621679948584YsSym1 p6989586621679948571
type Apply (Let6989586621679948584X_6989586621679948585Sym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] ([k], [k]) -> Type) -> Type) -> Type) (p6989586621679948571 :: k ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948584X_6989586621679948585Sym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] ([k], [k]) -> Type) -> Type) -> Type) (p6989586621679948571 :: k ~> Bool) = Let6989586621679948584X_6989586621679948585Sym1 p6989586621679948571
type Apply (Let6989586621679948627ZsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621679948614 :: k ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948627ZsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621679948614 :: k ~> Bool) = Let6989586621679948627ZsSym1 p6989586621679948614
type Apply (Let6989586621679948627YsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621679948614 :: k ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948627YsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621679948614 :: k ~> Bool) = Let6989586621679948627YsSym1 p6989586621679948614
type Apply (Let6989586621679948627X_6989586621679948628Sym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] ([k], [k]) -> Type) -> Type) -> Type) (p6989586621679948614 :: k ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948627X_6989586621679948628Sym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] ([k], [k]) -> Type) -> Type) -> Type) (p6989586621679948614 :: k ~> Bool) = Let6989586621679948627X_6989586621679948628Sym1 p6989586621679948614
type Apply (ListnubBySym0 :: TyFun (a6989586621680386742 ~> (a6989586621680386742 ~> Bool)) ([a6989586621680386742] ~> [a6989586621680386742]) -> Type) (a6989586621680387765 :: a6989586621680386742 ~> (a6989586621680386742 ~> Bool)) 
Instance details

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

type Apply (ListnubBySym0 :: TyFun (a6989586621680386742 ~> (a6989586621680386742 ~> Bool)) ([a6989586621680386742] ~> [a6989586621680386742]) -> Type) (a6989586621680387765 :: a6989586621680386742 ~> (a6989586621680386742 ~> Bool)) = ListnubBySym1 a6989586621680387765
type Apply (ListpartitionSym0 :: TyFun (a6989586621680386750 ~> Bool) ([a6989586621680386750] ~> ([a6989586621680386750], [a6989586621680386750])) -> Type) (a6989586621680387820 :: a6989586621680386750 ~> Bool) 
Instance details

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

type Apply (ListpartitionSym0 :: TyFun (a6989586621680386750 ~> Bool) ([a6989586621680386750] ~> ([a6989586621680386750], [a6989586621680386750])) -> Type) (a6989586621680387820 :: a6989586621680386750 ~> Bool) = ListpartitionSym1 a6989586621680387820
type Apply (ListfilterSym0 :: TyFun (a6989586621680386751 ~> Bool) ([a6989586621680386751] ~> [a6989586621680386751]) -> Type) (a6989586621680387830 :: a6989586621680386751 ~> Bool) 
Instance details

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

type Apply (ListfilterSym0 :: TyFun (a6989586621680386751 ~> Bool) ([a6989586621680386751] ~> [a6989586621680386751]) -> Type) (a6989586621680387830 :: a6989586621680386751 ~> Bool) = ListfilterSym1 a6989586621680387830
type Apply (ListspanSym0 :: TyFun (a6989586621680386752 ~> Bool) ([a6989586621680386752] ~> ([a6989586621680386752], [a6989586621680386752])) -> Type) (a6989586621680387840 :: a6989586621680386752 ~> Bool) 
Instance details

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

type Apply (ListspanSym0 :: TyFun (a6989586621680386752 ~> Bool) ([a6989586621680386752] ~> ([a6989586621680386752], [a6989586621680386752])) -> Type) (a6989586621680387840 :: a6989586621680386752 ~> Bool) = ListspanSym1 a6989586621680387840
type Apply (ListdropWhileSym0 :: TyFun (a6989586621680386753 ~> Bool) ([a6989586621680386753] ~> [a6989586621680386753]) -> Type) (a6989586621680387850 :: a6989586621680386753 ~> Bool) 
Instance details

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

type Apply (ListdropWhileSym0 :: TyFun (a6989586621680386753 ~> Bool) ([a6989586621680386753] ~> [a6989586621680386753]) -> Type) (a6989586621680387850 :: a6989586621680386753 ~> Bool) = ListdropWhileSym1 a6989586621680387850
type Apply (ListtakeWhileSym0 :: TyFun (a6989586621680386754 ~> Bool) ([a6989586621680386754] ~> [a6989586621680386754]) -> Type) (a6989586621680387860 :: a6989586621680386754 ~> Bool) 
Instance details

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

type Apply (ListtakeWhileSym0 :: TyFun (a6989586621680386754 ~> Bool) ([a6989586621680386754] ~> [a6989586621680386754]) -> Type) (a6989586621680387860 :: a6989586621680386754 ~> Bool) = ListtakeWhileSym1 a6989586621680387860
type Apply (NubBySym0 :: TyFun (a6989586621679939144 ~> (a6989586621679939144 ~> Bool)) ([a6989586621679939144] ~> [a6989586621679939144]) -> Type) (a6989586621679948411 :: a6989586621679939144 ~> (a6989586621679939144 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (NubBySym0 :: TyFun (a6989586621679939144 ~> (a6989586621679939144 ~> Bool)) ([a6989586621679939144] ~> [a6989586621679939144]) -> Type) (a6989586621679948411 :: a6989586621679939144 ~> (a6989586621679939144 ~> Bool)) = NubBySym1 a6989586621679948411
type Apply (PartitionSym0 :: TyFun (a6989586621679939153 ~> Bool) ([a6989586621679939153] ~> ([a6989586621679939153], [a6989586621679939153])) -> Type) (a6989586621679948509 :: a6989586621679939153 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (PartitionSym0 :: TyFun (a6989586621679939153 ~> Bool) ([a6989586621679939153] ~> ([a6989586621679939153], [a6989586621679939153])) -> Type) (a6989586621679948509 :: a6989586621679939153 ~> Bool) = PartitionSym1 a6989586621679948509
type Apply (BreakSym0 :: TyFun (a6989586621679939165 ~> Bool) ([a6989586621679939165] ~> ([a6989586621679939165], [a6989586621679939165])) -> Type) (a6989586621679948566 :: a6989586621679939165 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (BreakSym0 :: TyFun (a6989586621679939165 ~> Bool) ([a6989586621679939165] ~> ([a6989586621679939165], [a6989586621679939165])) -> Type) (a6989586621679948566 :: a6989586621679939165 ~> Bool) = BreakSym1 a6989586621679948566
type Apply (SpanSym0 :: TyFun (a6989586621679939166 ~> Bool) ([a6989586621679939166] ~> ([a6989586621679939166], [a6989586621679939166])) -> Type) (a6989586621679948609 :: a6989586621679939166 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (SpanSym0 :: TyFun (a6989586621679939166 ~> Bool) ([a6989586621679939166] ~> ([a6989586621679939166], [a6989586621679939166])) -> Type) (a6989586621679948609 :: a6989586621679939166 ~> Bool) = SpanSym1 a6989586621679948609
type Apply (GroupBySym0 :: TyFun (a6989586621679939156 ~> (a6989586621679939156 ~> Bool)) ([a6989586621679939156] ~> [[a6989586621679939156]]) -> Type) (a6989586621679948652 :: a6989586621679939156 ~> (a6989586621679939156 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (GroupBySym0 :: TyFun (a6989586621679939156 ~> (a6989586621679939156 ~> Bool)) ([a6989586621679939156] ~> [[a6989586621679939156]]) -> Type) (a6989586621679948652 :: a6989586621679939156 ~> (a6989586621679939156 ~> Bool)) = GroupBySym1 a6989586621679948652
type Apply (DropWhileSym0 :: TyFun (a6989586621679939168 ~> Bool) ([a6989586621679939168] ~> [a6989586621679939168]) -> Type) (a6989586621679948686 :: a6989586621679939168 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DropWhileSym0 :: TyFun (a6989586621679939168 ~> Bool) ([a6989586621679939168] ~> [a6989586621679939168]) -> Type) (a6989586621679948686 :: a6989586621679939168 ~> Bool) = DropWhileSym1 a6989586621679948686
type Apply (TakeWhileSym0 :: TyFun (a6989586621679939169 ~> Bool) ([a6989586621679939169] ~> [a6989586621679939169]) -> Type) (a6989586621679948704 :: a6989586621679939169 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (TakeWhileSym0 :: TyFun (a6989586621679939169 ~> Bool) ([a6989586621679939169] ~> [a6989586621679939169]) -> Type) (a6989586621679948704 :: a6989586621679939169 ~> Bool) = TakeWhileSym1 a6989586621679948704
type Apply (FilterSym0 :: TyFun (a6989586621679939177 ~> Bool) ([a6989586621679939177] ~> [a6989586621679939177]) -> Type) (a6989586621679948718 :: a6989586621679939177 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FilterSym0 :: TyFun (a6989586621679939177 ~> Bool) ([a6989586621679939177] ~> [a6989586621679939177]) -> Type) (a6989586621679948718 :: a6989586621679939177 ~> Bool) = FilterSym1 a6989586621679948718
type Apply (FindSym0 :: TyFun (a6989586621679939176 ~> Bool) ([a6989586621679939176] ~> Maybe a6989586621679939176) -> Type) (a6989586621679948733 :: a6989586621679939176 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FindSym0 :: TyFun (a6989586621679939176 ~> Bool) ([a6989586621679939176] ~> Maybe a6989586621679939176) -> Type) (a6989586621679948733 :: a6989586621679939176 ~> Bool) = FindSym1 a6989586621679948733
type Apply (DeleteFirstsBySym0 :: TyFun (a6989586621679939182 ~> (a6989586621679939182 ~> Bool)) ([a6989586621679939182] ~> ([a6989586621679939182] ~> [a6989586621679939182])) -> Type) (a6989586621679948802 :: a6989586621679939182 ~> (a6989586621679939182 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DeleteFirstsBySym0 :: TyFun (a6989586621679939182 ~> (a6989586621679939182 ~> Bool)) ([a6989586621679939182] ~> ([a6989586621679939182] ~> [a6989586621679939182])) -> Type) (a6989586621679948802 :: a6989586621679939182 ~> (a6989586621679939182 ~> Bool)) = DeleteFirstsBySym1 a6989586621679948802
type Apply (UnionBySym0 :: TyFun (a6989586621679939142 ~> (a6989586621679939142 ~> Bool)) ([a6989586621679939142] ~> ([a6989586621679939142] ~> [a6989586621679939142])) -> Type) (a6989586621679948815 :: a6989586621679939142 ~> (a6989586621679939142 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (UnionBySym0 :: TyFun (a6989586621679939142 ~> (a6989586621679939142 ~> Bool)) ([a6989586621679939142] ~> ([a6989586621679939142] ~> [a6989586621679939142])) -> Type) (a6989586621679948815 :: a6989586621679939142 ~> (a6989586621679939142 ~> Bool)) = UnionBySym1 a6989586621679948815
type Apply (FindIndicesSym0 :: TyFun (a6989586621679939172 ~> Bool) ([a6989586621679939172] ~> [Nat]) -> Type) (a6989586621679949059 :: a6989586621679939172 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FindIndicesSym0 :: TyFun (a6989586621679939172 ~> Bool) ([a6989586621679939172] ~> [Nat]) -> Type) (a6989586621679949059 :: a6989586621679939172 ~> Bool) = FindIndicesSym1 a6989586621679949059
type Apply (FindIndexSym0 :: TyFun (a6989586621679939173 ~> Bool) ([a6989586621679939173] ~> Maybe Nat) -> Type) (a6989586621679949093 :: a6989586621679939173 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FindIndexSym0 :: TyFun (a6989586621679939173 ~> Bool) ([a6989586621679939173] ~> Maybe Nat) -> Type) (a6989586621679949093 :: a6989586621679939173 ~> Bool) = FindIndexSym1 a6989586621679949093
type Apply (AnySym0 :: TyFun (a6989586621679939246 ~> Bool) ([a6989586621679939246] ~> Bool) -> Type) (a6989586621679949374 :: a6989586621679939246 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (AnySym0 :: TyFun (a6989586621679939246 ~> Bool) ([a6989586621679939246] ~> Bool) -> Type) (a6989586621679949374 :: a6989586621679939246 ~> Bool) = AnySym1 a6989586621679949374
type Apply (IntersectBySym0 :: TyFun (a6989586621679939170 ~> (a6989586621679939170 ~> Bool)) ([a6989586621679939170] ~> ([a6989586621679939170] ~> [a6989586621679939170])) -> Type) (a6989586621679949387 :: a6989586621679939170 ~> (a6989586621679939170 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IntersectBySym0 :: TyFun (a6989586621679939170 ~> (a6989586621679939170 ~> Bool)) ([a6989586621679939170] ~> ([a6989586621679939170] ~> [a6989586621679939170])) -> Type) (a6989586621679949387 :: a6989586621679939170 ~> (a6989586621679939170 ~> Bool)) = IntersectBySym1 a6989586621679949387
type Apply (AllSym0 :: TyFun (a6989586621679939247 ~> Bool) ([a6989586621679939247] ~> Bool) -> Type) (a6989586621679949429 :: a6989586621679939247 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (AllSym0 :: TyFun (a6989586621679939247 ~> Bool) ([a6989586621679939247] ~> Bool) -> Type) (a6989586621679949429 :: a6989586621679939247 ~> Bool) = AllSym1 a6989586621679949429
type Apply (DropWhileEndSym0 :: TyFun (a6989586621679939167 ~> Bool) ([a6989586621679939167] ~> [a6989586621679939167]) -> Type) (a6989586621679949742 :: a6989586621679939167 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DropWhileEndSym0 :: TyFun (a6989586621679939167 ~> Bool) ([a6989586621679939167] ~> [a6989586621679939167]) -> Type) (a6989586621679949742 :: a6989586621679939167 ~> Bool) = DropWhileEndSym1 a6989586621679949742
type Apply (Elem_bySym0 :: TyFun (a6989586621679939143 ~> (a6989586621679939143 ~> Bool)) (a6989586621679939143 ~> ([a6989586621679939143] ~> Bool)) -> Type) (a6989586621679948401 :: a6989586621679939143 ~> (a6989586621679939143 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Elem_bySym0 :: TyFun (a6989586621679939143 ~> (a6989586621679939143 ~> Bool)) (a6989586621679939143 ~> ([a6989586621679939143] ~> Bool)) -> Type) (a6989586621679948401 :: a6989586621679939143 ~> (a6989586621679939143 ~> Bool)) = Elem_bySym1 a6989586621679948401
type Apply (SelectSym0 :: TyFun (a6989586621679939152 ~> Bool) (a6989586621679939152 ~> (([a6989586621679939152], [a6989586621679939152]) ~> ([a6989586621679939152], [a6989586621679939152]))) -> Type) (a6989586621679948491 :: a6989586621679939152 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (SelectSym0 :: TyFun (a6989586621679939152 ~> Bool) (a6989586621679939152 ~> (([a6989586621679939152], [a6989586621679939152]) ~> ([a6989586621679939152], [a6989586621679939152]))) -> Type) (a6989586621679948491 :: a6989586621679939152 ~> Bool) = SelectSym1 a6989586621679948491
type Apply (DeleteBySym0 :: TyFun (a6989586621679939183 ~> (a6989586621679939183 ~> Bool)) (a6989586621679939183 ~> ([a6989586621679939183] ~> [a6989586621679939183])) -> Type) (a6989586621679948784 :: a6989586621679939183 ~> (a6989586621679939183 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DeleteBySym0 :: TyFun (a6989586621679939183 ~> (a6989586621679939183 ~> Bool)) (a6989586621679939183 ~> ([a6989586621679939183] ~> [a6989586621679939183])) -> Type) (a6989586621679948784 :: a6989586621679939183 ~> (a6989586621679939183 ~> Bool)) = DeleteBySym1 a6989586621679948784
type Apply (UntilSym0 :: TyFun (a6989586621679519853 ~> Bool) ((a6989586621679519853 ~> a6989586621679519853) ~> (a6989586621679519853 ~> a6989586621679519853)) -> Type) (a6989586621679519978 :: a6989586621679519853 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (UntilSym0 :: TyFun (a6989586621679519853 ~> Bool) ((a6989586621679519853 ~> a6989586621679519853) ~> (a6989586621679519853 ~> a6989586621679519853)) -> Type) (a6989586621679519978 :: a6989586621679519853 ~> Bool) = UntilSym1 a6989586621679519978
type Apply (Let6989586621679948417NubBy'Sym0 :: TyFun (k1 ~> (k1 ~> Bool)) (TyFun k (TyFun [k1] ([k1] ~> [k1]) -> Type) -> Type) -> Type) (eq6989586621679948415 :: k1 ~> (k1 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948417NubBy'Sym0 :: TyFun (k1 ~> (k1 ~> Bool)) (TyFun k (TyFun [k1] ([k1] ~> [k1]) -> Type) -> Type) -> Type) (eq6989586621679948415 :: k1 ~> (k1 ~> Bool)) = (Let6989586621679948417NubBy'Sym1 eq6989586621679948415 :: TyFun k (TyFun [k1] ([k1] ~> [k1]) -> Type) -> Type)
type Apply (Let6989586621679948659ZsSym0 :: TyFun (k1 ~> (a6989586621679939166 ~> Bool)) (TyFun k1 (TyFun [a6989586621679939166] [a6989586621679939166] -> Type) -> Type) -> Type) (eq6989586621679948656 :: k1 ~> (a6989586621679939166 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948659ZsSym0 :: TyFun (k1 ~> (a6989586621679939166 ~> Bool)) (TyFun k1 (TyFun [a6989586621679939166] [a6989586621679939166] -> Type) -> Type) -> Type) (eq6989586621679948656 :: k1 ~> (a6989586621679939166 ~> Bool)) = Let6989586621679948659ZsSym1 eq6989586621679948656
type Apply (Let6989586621679948659YsSym0 :: TyFun (k1 ~> (a6989586621679939166 ~> Bool)) (TyFun k1 (TyFun [a6989586621679939166] [a6989586621679939166] -> Type) -> Type) -> Type) (eq6989586621679948656 :: k1 ~> (a6989586621679939166 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948659YsSym0 :: TyFun (k1 ~> (a6989586621679939166 ~> Bool)) (TyFun k1 (TyFun [a6989586621679939166] [a6989586621679939166] -> Type) -> Type) -> Type) (eq6989586621679948656 :: k1 ~> (a6989586621679939166 ~> Bool)) = Let6989586621679948659YsSym1 eq6989586621679948656
type Apply (Let6989586621679948659X_6989586621679948660Sym0 :: TyFun (k1 ~> (a6989586621679939166 ~> Bool)) (TyFun k1 (TyFun [a6989586621679939166] ([a6989586621679939166], [a6989586621679939166]) -> Type) -> Type) -> Type) (eq6989586621679948656 :: k1 ~> (a6989586621679939166 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948659X_6989586621679948660Sym0 :: TyFun (k1 ~> (a6989586621679939166 ~> Bool)) (TyFun k1 (TyFun [a6989586621679939166] ([a6989586621679939166], [a6989586621679939166]) -> Type) -> Type) -> Type) (eq6989586621679948656 :: k1 ~> (a6989586621679939166 ~> Bool)) = Let6989586621679948659X_6989586621679948660Sym1 eq6989586621679948656
type Apply (Lambda_6989586621679949750Sym0 :: TyFun (a6989586621679939263 ~> Bool) (TyFun k (TyFun a6989586621679939263 (TyFun [a6989586621679939263] [a6989586621679939263] -> Type) -> Type) -> Type) -> Type) (p6989586621679949748 :: a6989586621679939263 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Lambda_6989586621679949750Sym0 :: TyFun (a6989586621679939263 ~> Bool) (TyFun k (TyFun a6989586621679939263 (TyFun [a6989586621679939263] [a6989586621679939263] -> Type) -> Type) -> Type) -> Type) (p6989586621679949748 :: a6989586621679939263 ~> Bool) = (Lambda_6989586621679949750Sym1 p6989586621679949748 :: TyFun k (TyFun a6989586621679939263 (TyFun [a6989586621679939263] [a6989586621679939263] -> Type) -> Type) -> Type)
type Apply (Lambda_6989586621680450574Sym0 :: TyFun (a6989586621679072633 ~> Bool) (TyFun k (TyFun a6989586621679072633 (First a6989586621679072633) -> Type) -> Type) -> Type) (p6989586621680450571 :: a6989586621679072633 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Lambda_6989586621680450574Sym0 :: TyFun (a6989586621679072633 ~> Bool) (TyFun k (TyFun a6989586621679072633 (First a6989586621679072633) -> Type) -> Type) -> Type) (p6989586621680450571 :: a6989586621679072633 ~> Bool) = (Lambda_6989586621680450574Sym1 p6989586621680450571 :: TyFun k (TyFun a6989586621679072633 (First a6989586621679072633) -> Type) -> Type)
type Apply (Let6989586621680450671Scrutinee_6989586621680450452Sym0 :: TyFun (a6989586621680450204 ~> Bool) (TyFun (t6989586621680450201 a6989586621680450204) Any -> Type) -> Type) (p6989586621680450669 :: a6989586621680450204 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680450671Scrutinee_6989586621680450452Sym0 :: TyFun (a6989586621680450204 ~> Bool) (TyFun (t6989586621680450201 a6989586621680450204) Any -> Type) -> Type) (p6989586621680450669 :: a6989586621680450204 ~> Bool) = (Let6989586621680450671Scrutinee_6989586621680450452Sym1 p6989586621680450669 :: TyFun (t6989586621680450201 a6989586621680450204) Any -> Type)
type Apply (Let6989586621680450658Scrutinee_6989586621680450454Sym0 :: TyFun (a6989586621680450204 ~> Bool) (TyFun (t6989586621680450201 a6989586621680450204) All -> Type) -> Type) (p6989586621680450656 :: a6989586621680450204 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680450658Scrutinee_6989586621680450454Sym0 :: TyFun (a6989586621680450204 ~> Bool) (TyFun (t6989586621680450201 a6989586621680450204) All -> Type) -> Type) (p6989586621680450656 :: a6989586621680450204 ~> Bool) = (Let6989586621680450658Scrutinee_6989586621680450454Sym1 p6989586621680450656 :: TyFun (t6989586621680450201 a6989586621680450204) All -> Type)
type Apply (Let6989586621680450573Scrutinee_6989586621680450460Sym0 :: TyFun (a6989586621680450204 ~> Bool) (TyFun (t6989586621680450201 a6989586621680450204) (First a6989586621680450204) -> Type) -> Type) (p6989586621680450571 :: a6989586621680450204 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680450573Scrutinee_6989586621680450460Sym0 :: TyFun (a6989586621680450204 ~> Bool) (TyFun (t6989586621680450201 a6989586621680450204) (First a6989586621680450204) -> Type) -> Type) (p6989586621680450571 :: a6989586621680450204 ~> Bool) = (Let6989586621680450573Scrutinee_6989586621680450460Sym1 p6989586621680450571 :: TyFun (t6989586621680450201 a6989586621680450204) (First a6989586621680450204) -> Type)
type Apply (Let6989586621679519989GoSym0 :: TyFun (k1 ~> Bool) (TyFun (k1 ~> k1) (TyFun k2 (TyFun k1 k1 -> Type) -> Type) -> Type) -> Type) (p6989586621679519986 :: k1 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (Let6989586621679519989GoSym0 :: TyFun (k1 ~> Bool) (TyFun (k1 ~> k1) (TyFun k2 (TyFun k1 k1 -> Type) -> Type) -> Type) -> Type) (p6989586621679519986 :: k1 ~> Bool) = (Let6989586621679519989GoSym1 p6989586621679519986 :: TyFun (k1 ~> k1) (TyFun k2 (TyFun k1 k1 -> Type) -> Type) -> Type)
type Apply (AnySym0 :: TyFun (a6989586621680450120 ~> Bool) (t6989586621680450119 a6989586621680450120 ~> Bool) -> Type) (a6989586621680450665 :: a6989586621680450120 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AnySym0 :: TyFun (a6989586621680450120 ~> Bool) (t6989586621680450119 a6989586621680450120 ~> Bool) -> Type) (a6989586621680450665 :: a6989586621680450120 ~> Bool) = (AnySym1 a6989586621680450665 t6989586621680450119 :: TyFun (t6989586621680450119 a6989586621680450120) Bool -> Type)
type Apply (AllSym0 :: TyFun (a6989586621680450118 ~> Bool) (t6989586621680450117 a6989586621680450118 ~> Bool) -> Type) (a6989586621680450652 :: a6989586621680450118 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AllSym0 :: TyFun (a6989586621680450118 ~> Bool) (t6989586621680450117 a6989586621680450118 ~> Bool) -> Type) (a6989586621680450652 :: a6989586621680450118 ~> Bool) = (AllSym1 a6989586621680450652 t6989586621680450117 :: TyFun (t6989586621680450117 a6989586621680450118) Bool -> Type)
type Apply (FindSym0 :: TyFun (a6989586621680450110 ~> Bool) (t6989586621680450109 a6989586621680450110 ~> Maybe a6989586621680450110) -> Type) (a6989586621680450567 :: a6989586621680450110 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FindSym0 :: TyFun (a6989586621680450110 ~> Bool) (t6989586621680450109 a6989586621680450110 ~> Maybe a6989586621680450110) -> Type) (a6989586621680450567 :: a6989586621680450110 ~> Bool) = (FindSym1 a6989586621680450567 t6989586621680450109 :: TyFun (t6989586621680450109 a6989586621680450110) (Maybe a6989586621680450110) -> Type)
type Apply (TFHelper_6989586621680882327Sym0 :: TyFun (Arg a6989586621680881110 b6989586621680881111) (Arg a6989586621680881110 b6989586621680881111 ~> Bool) -> Type) (a6989586621680882325 :: Arg a6989586621680881110 b6989586621680881111) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Apply (TFHelper_6989586621680882327Sym0 :: TyFun (Arg a6989586621680881110 b6989586621680881111) (Arg a6989586621680881110 b6989586621680881111 ~> Bool) -> Type) (a6989586621680882325 :: Arg a6989586621680881110 b6989586621680881111) = TFHelper_6989586621680882327Sym1 a6989586621680882325
type Apply (Let6989586621679948427Scrutinee_6989586621679939850Sym0 :: TyFun (k1 ~> (k1 ~> Bool)) (TyFun k2 (TyFun k1 (TyFun k3 (TyFun [k1] Bool -> Type) -> Type) -> Type) -> Type) -> Type) (eq6989586621679948415 :: k1 ~> (k1 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948427Scrutinee_6989586621679939850Sym0 :: TyFun (k1 ~> (k1 ~> Bool)) (TyFun k2 (TyFun k1 (TyFun k3 (TyFun [k1] Bool -> Type) -> Type) -> Type) -> Type) -> Type) (eq6989586621679948415 :: k1 ~> (k1 ~> Bool)) = (Let6989586621679948427Scrutinee_6989586621679939850Sym1 eq6989586621679948415 :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun [k1] Bool -> Type) -> Type) -> Type) -> Type)
type Apply (Let6989586621679949754Scrutinee_6989586621679939822Sym0 :: TyFun (k1 ~> Bool) (TyFun k1 (TyFun [a6989586621679939263] (TyFun k Bool -> Type) -> Type) -> Type) -> Type) (p6989586621679949748 :: k1 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679949754Scrutinee_6989586621679939822Sym0 :: TyFun (k1 ~> Bool) (TyFun k1 (TyFun [a6989586621679939263] (TyFun k Bool -> Type) -> Type) -> Type) -> Type) (p6989586621679949748 :: k1 ~> Bool) = (Let6989586621679949754Scrutinee_6989586621679939822Sym1 p6989586621679949748 :: TyFun k1 (TyFun [a6989586621679939263] (TyFun k Bool -> Type) -> Type) -> Type)
type Apply (Lambda_6989586621679949409Sym0 :: TyFun (b6989586621679544177 ~> (a6989586621679939246 ~> Bool)) (TyFun k1 (TyFun k2 (TyFun a6989586621679939246 (TyFun [a6989586621679939246] (TyFun b6989586621679544177 (m6989586621679544173 b6989586621679544177) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (eq6989586621679949393 :: b6989586621679544177 ~> (a6989586621679939246 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Lambda_6989586621679949409Sym0 :: TyFun (b6989586621679544177 ~> (a6989586621679939246 ~> Bool)) (TyFun k1 (TyFun k2 (TyFun a6989586621679939246 (TyFun [a6989586621679939246] (TyFun b6989586621679544177 (m6989586621679544173 b6989586621679544177) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (eq6989586621679949393 :: b6989586621679544177 ~> (a6989586621679939246 ~> Bool)) = (Lambda_6989586621679949409Sym1 eq6989586621679949393 :: TyFun k1 (TyFun k2 (TyFun a6989586621679939246 (TyFun [a6989586621679939246] (TyFun b6989586621679544177 (m6989586621679544173 b6989586621679544177) -> Type) -> Type) -> Type) -> Type) -> 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
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 :: (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 
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 :: Type #

NFData ByteString 
Instance details

Defined in Data.ByteString.Internal

Methods

rnf :: ByteString -> () #

ByteArray ByteString 
Instance details

Defined in Data.ByteArray.Types

Methods

allocRet :: Int -> (Ptr p -> IO a) -> IO (a, ByteString) #

ByteArrayAccess ByteString 
Instance details

Defined in Data.ByteArray.Types

Methods

length :: ByteString -> Int #

withByteArray :: ByteString -> (Ptr p -> IO a) -> IO a #

copyByteArrayToPtr :: ByteString -> Ptr p -> IO () #

FormatAsHex ByteString 
Instance details

Defined in Fmt.Internal

Methods

hexF :: ByteString -> Builder #

FormatAsBase64 ByteString 
Instance details

Defined in Fmt.Internal

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 #

type Tokens ByteString :: Type #

One ByteString 
Instance details

Defined in Universum.Container.Class

Associated Types

type OneItem ByteString :: Type #

Container ByteString 
Instance details

Defined in Universum.Container.Class

Associated Types

type Element ByteString :: Type #

Print ByteString 
Instance details

Defined in Universum.Print.Internal

Methods

hPutStr :: Handle -> ByteString -> IO () #

hPutStrLn :: Handle -> ByteString -> IO () #

IsoValue ByteString Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT ByteString :: T Source #

IsoCValue ByteString Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToCT ByteString :: CT Source #

TypeHasDoc ByteString Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

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

CompareOpHs ByteString Source # 
Instance details

Defined in Lorentz.Arith

Strict ByteString ByteString 
Instance details

Defined in Control.Lens.Iso

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

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 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 OneItem ByteString 
Instance details

Defined in Universum.Container.Class

type Element ByteString 
Instance details

Defined in Universum.Container.Class

type ToT ByteString Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToCT ByteString Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

data Address Source #

Data type corresponding to address structure in Tezos.

Instances
Eq Address Source # 
Instance details

Defined in Tezos.Address

Methods

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

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

Ord Address Source # 
Instance details

Defined in Tezos.Address

Show Address Source # 
Instance details

Defined in Tezos.Address

Arbitrary Address Source # 
Instance details

Defined in Tezos.Address

ToJSON Address Source # 
Instance details

Defined in Tezos.Address

ToJSONKey Address Source # 
Instance details

Defined in Tezos.Address

FromJSON Address Source # 
Instance details

Defined in Tezos.Address

FromJSONKey Address Source # 
Instance details

Defined in Tezos.Address

Buildable Address Source # 
Instance details

Defined in Tezos.Address

Methods

build :: Address -> Builder #

IsoValue Address Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Address :: T Source #

IsoCValue Address Source #

This instance erases reference to contract entrypoint! If this is an issue, use EpAddress instead.

Applications which use addresses just as participants identifiers should not experience problems with using plain Address.

Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToCT Address :: CT Source #

TypeHasDoc Address Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

ToAddress Address Source # 
Instance details

Defined in Lorentz.Value

CompareOpHs Address Source # 
Instance details

Defined in Lorentz.Arith

FromContractRef cp Address Source # 
Instance details

Defined in Lorentz.Value

NiceParameter cp => ToContractRef cp Address Source #

Make contract ref calling the default entrypoint.

Instance details

Defined in Lorentz.Value

type ToT Address Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToCT Address Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

data EpAddress Source #

Address with optional entrypoint name attached to it. TODO: come up with better name?

Constructors

EpAddress 

Fields

Instances
Eq EpAddress Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Ord EpAddress Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Show EpAddress Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Arbitrary FieldAnn => Arbitrary EpAddress Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Buildable EpAddress Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Methods

build :: EpAddress -> Builder #

IsoValue EpAddress Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT EpAddress :: T Source #

IsoCValue EpAddress Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToCT EpAddress :: CT Source #

TypeHasDoc EpAddress Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

ToAddress EpAddress Source # 
Instance details

Defined in Lorentz.Value

CompareOpHs EpAddress Source # 
Instance details

Defined in Lorentz.Arith

FromContractRef cp EpAddress Source # 
Instance details

Defined in Lorentz.Value

NiceParameter cp => ToContractRef cp EpAddress Source # 
Instance details

Defined in Lorentz.Value

type ToT EpAddress Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToCT EpAddress Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

data Mutez Source #

Mutez is a wrapper over integer data type. 1 mutez is 1 token (μTz).

Instances
Bounded Mutez Source # 
Instance details

Defined in Tezos.Core

Enum Mutez Source # 
Instance details

Defined in Tezos.Core

Eq Mutez Source # 
Instance details

Defined in Tezos.Core

Methods

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

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

Data Mutez Source # 
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 :: (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 Source # 
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 Source # 
Instance details

Defined in Tezos.Core

Methods

showsPrec :: Int -> Mutez -> ShowS #

show :: Mutez -> String #

showList :: [Mutez] -> ShowS #

Generic Mutez Source # 
Instance details

Defined in Tezos.Core

Associated Types

type Rep Mutez :: Type -> Type #

Methods

from :: Mutez -> Rep Mutez x #

to :: Rep Mutez x -> Mutez #

Arbitrary Mutez Source # 
Instance details

Defined in Michelson.Test.Gen

Methods

arbitrary :: Gen Mutez #

shrink :: Mutez -> [Mutez] #

ToJSON Mutez Source # 
Instance details

Defined in Tezos.Core

FromJSON Mutez Source # 
Instance details

Defined in Tezos.Core

Buildable Mutez Source # 
Instance details

Defined in Tezos.Core

Methods

build :: Mutez -> Builder #

ToADTArbitrary Mutez Source # 
Instance details

Defined in Util.Test.Arbitrary

IsoValue Mutez Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Mutez :: T Source #

IsoCValue Mutez Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToCT Mutez :: CT Source #

TypeHasDoc Mutez Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

CompareOpHs Mutez Source # 
Instance details

Defined in Lorentz.Arith

EDivOpHs Mutez Natural Source # 
Instance details

Defined in Lorentz.Polymorphic

EDivOpHs Mutez Mutez Source # 
Instance details

Defined in Lorentz.Polymorphic

ArithOpHs Mul Natural Mutez Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Natural Mutez :: Type Source #

ArithOpHs Mul Mutez Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Mutez Natural :: Type Source #

ArithOpHs Sub Mutez Mutez Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Sub Mutez Mutez :: Type Source #

ArithOpHs Add Mutez Mutez Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Mutez Mutez :: Type Source #

type Rep Mutez Source # 
Instance details

Defined in Tezos.Core

type Rep Mutez = D1 (MetaData "Mutez" "Tezos.Core" "morley-0.5.0-GrlgowF8t30F9AnUlsv4ov" True) (C1 (MetaCons "Mutez" PrefixI True) (S1 (MetaSel (Just "unMutez") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64)))
type ToT Mutez Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT Mutez = Tc (ToCT Mutez)
type ToCT Mutez Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

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 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

type ArithResHs Add Mutez Mutez Source # 
Instance details

Defined in Lorentz.Arith

data Timestamp Source #

Time in the real world. Use the functions below to convert it to/from Unix time in seconds.

Instances
Eq Timestamp Source # 
Instance details

Defined in Tezos.Core

Data Timestamp Source # 
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 :: (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 Source # 
Instance details

Defined in Tezos.Core

Show Timestamp Source # 
Instance details

Defined in Tezos.Core

Generic Timestamp Source # 
Instance details

Defined in Tezos.Core

Associated Types

type Rep Timestamp :: Type -> Type #

Arbitrary Timestamp Source # 
Instance details

Defined in Michelson.Test.Gen

ToJSON Timestamp Source # 
Instance details

Defined in Tezos.Core

FromJSON Timestamp Source # 
Instance details

Defined in Tezos.Core

Buildable Timestamp Source # 
Instance details

Defined in Tezos.Core

Methods

build :: Timestamp -> Builder #

IsoValue Timestamp Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Timestamp :: T Source #

IsoCValue Timestamp Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToCT Timestamp :: CT Source #

TypeHasDoc Timestamp Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

CompareOpHs Timestamp Source # 
Instance details

Defined in Lorentz.Arith

ArithOpHs Sub Timestamp Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Sub Timestamp Integer :: Type Source #

ArithOpHs Sub Timestamp Timestamp Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Sub Timestamp Timestamp :: Type Source #

ArithOpHs Add Integer Timestamp Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Integer Timestamp :: Type Source #

ArithOpHs Add Timestamp Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Timestamp Integer :: Type Source #

type Rep Timestamp Source # 
Instance details

Defined in Tezos.Core

type Rep Timestamp = D1 (MetaData "Timestamp" "Tezos.Core" "morley-0.5.0-GrlgowF8t30F9AnUlsv4ov" True) (C1 (MetaCons "Timestamp" PrefixI True) (S1 (MetaSel (Just "unTimestamp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 POSIXTime)))
type ToT Timestamp Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToCT Timestamp Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ArithResHs Sub Timestamp Integer Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Sub Timestamp Timestamp Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Add Integer Timestamp Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Add Timestamp Integer Source # 
Instance details

Defined in Lorentz.Arith

data ChainId Source #

Identifier of a network (babylonnet, mainnet, test network or other). Evaluated as hash of the genesis block.

The only operation supported for this type is packing. Use case: multisig contract, for instance, now includes chain ID into signed data "in order to add extra replay protection between the main chain and the test chain".

Instances
Eq ChainId Source # 
Instance details

Defined in Tezos.Core

Methods

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

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

Show ChainId Source # 
Instance details

Defined in Tezos.Core

Arbitrary ChainId Source # 
Instance details

Defined in Tezos.Core

ToJSON ChainId Source # 
Instance details

Defined in Tezos.Core

FromJSON ChainId Source # 
Instance details

Defined in Tezos.Core

Buildable ChainId Source # 
Instance details

Defined in Tezos.Core

Methods

build :: ChainId -> Builder #

IsoValue ChainId Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT ChainId :: T Source #

type ToT ChainId Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

data KeyHash Source #

Blake2b_160 hash of a public key.

Instances
Eq KeyHash Source # 
Instance details

Defined in Tezos.Crypto

Methods

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

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

Ord KeyHash Source # 
Instance details

Defined in Tezos.Crypto

Show KeyHash Source # 
Instance details

Defined in Tezos.Crypto

Arbitrary KeyHash Source # 
Instance details

Defined in Tezos.Crypto

ToJSON KeyHash Source # 
Instance details

Defined in Tezos.Crypto

FromJSON KeyHash Source # 
Instance details

Defined in Tezos.Crypto

Buildable KeyHash Source # 
Instance details

Defined in Tezos.Crypto

Methods

build :: KeyHash -> Builder #

IsoValue KeyHash Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT KeyHash :: T Source #

IsoCValue KeyHash Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToCT KeyHash :: CT Source #

TypeHasDoc KeyHash Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

CompareOpHs KeyHash Source # 
Instance details

Defined in Lorentz.Arith

type ToT KeyHash Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToCT KeyHash Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

data PublicKey Source #

Public cryptographic key used by Tezos. There are three cryptographic curves each represented by its own constructor.

Instances
Eq PublicKey Source # 
Instance details

Defined in Tezos.Crypto

Show PublicKey Source # 
Instance details

Defined in Tezos.Crypto

Arbitrary PublicKey Source # 
Instance details

Defined in Tezos.Crypto

ToJSON PublicKey Source # 
Instance details

Defined in Tezos.Crypto

FromJSON PublicKey Source # 
Instance details

Defined in Tezos.Crypto

Buildable PublicKey Source # 
Instance details

Defined in Tezos.Crypto

Methods

build :: PublicKey -> Builder #

IsoValue PublicKey Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT PublicKey :: T Source #

TypeHasDoc PublicKey Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type ToT PublicKey Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

data Signature Source #

Cryptographic signatures used by Tezos. Constructors correspond to PublicKey constructors.

Tezos distinguishes signatures for different curves. For instance, ed25519 signatures and secp256k1 signatures are printed differently (have different prefix). However, signatures are packed without information about the curve. For this purpose there is a generic signature which only stores bytes and doesn't carry information about the curve. Apparently unpacking from bytes always produces such signature. Unpacking from string produces a signature with curve information.

Instances
Eq Signature Source # 
Instance details

Defined in Tezos.Crypto

Show Signature Source # 
Instance details

Defined in Tezos.Crypto

Arbitrary Signature Source # 
Instance details

Defined in Tezos.Crypto

ToJSON Signature Source # 
Instance details

Defined in Tezos.Crypto

FromJSON Signature Source # 
Instance details

Defined in Tezos.Crypto

Buildable Signature Source # 
Instance details

Defined in Tezos.Crypto

Methods

build :: Signature -> Builder #

IsoValue Signature Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Signature :: T Source #

TypeHasDoc Signature Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type ToT Signature Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

data Set a #

A set of values a.

Instances
Foldable Set 
Instance details

Defined in Data.Set.Internal

Methods

fold :: Monoid m => Set m -> 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) :: Type #

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 :: (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 #

(Ord a, Arbitrary a) => Arbitrary (Set a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Set a) #

shrink :: Set a -> [Set a] #

CoArbitrary a => CoArbitrary (Set a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

coarbitrary :: Set a -> Gen b -> Gen b #

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 #

(Ord a, FromJSON a) => FromJSON (Set a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Set a) #

parseJSONList :: Value -> Parser [Set a] #

NFData a => NFData (Set a) 
Instance details

Defined in Data.Set.Internal

Methods

rnf :: Set a -> () #

Buildable' v => Buildable' (Set v) 
Instance details

Defined in Fmt.Internal.Generic

Methods

build' :: Set v -> Builder #

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) :: Type #

Methods

_Wrapped' :: Iso' (Set a) (Unwrapped (Set a)) #

One (Set v) 
Instance details

Defined in Universum.Container.Class

Associated Types

type OneItem (Set v) :: Type #

Methods

one :: OneItem (Set v) -> Set v #

Ord v => Container (Set v) 
Instance details

Defined in Universum.Container.Class

Associated Types

type Element (Set v) :: Type #

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

(Ord c, IsoCValue c) => IsoValue (Set c) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (Set c) :: T Source #

Methods

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

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

PolyCTypeHasDocC (a ': ([] :: [Type])) => TypeHasDoc (Set a) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

IsComparable a => UpdOpHs (Set a) Source # 
Instance details

Defined in Lorentz.Polymorphic

Associated Types

type UpdOpKeyHs (Set a) :: Type Source #

type UpdOpParamsHs (Set a) :: Type Source #

SizeOpHs (Set a) Source # 
Instance details

Defined in Lorentz.Polymorphic

IsComparable e => IterOpHs (Set e) Source # 
Instance details

Defined in Lorentz.Polymorphic

Associated Types

type IterOpElHs (Set e) :: Type Source #

IsComparable e => MemOpHs (Set e) Source # 
Instance details

Defined in Lorentz.Polymorphic

Associated Types

type MemOpKeyHs (Set e) :: Type 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

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 OneItem (Set v) 
Instance details

Defined in Universum.Container.Class

type OneItem (Set v) = v
type Element (Set v) 
Instance details

Defined in Universum.Container.Class

type Element (Set v) = ElementDefault (Set v)
type ToT (Set c) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT (Set c) = TSet (ToCT 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.

Instances
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 #

Ord k => TraverseMin k (Map k) 
Instance details

Defined in Control.Lens.Traversal

Methods

traverseMin :: IndexedTraversal' k (Map k v) v #

Ord k => TraverseMax k (Map k) 
Instance details

Defined in Control.Lens.Traversal

Methods

traverseMax :: IndexedTraversal' k (Map k v) v #

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) 
Instance details

Defined in Data.Map.Internal

Methods

fold :: Monoid m => Map k m -> 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) 
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) #

(Ord k, Arbitrary k) => Arbitrary1 (Map k) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

liftArbitrary :: Gen a -> Gen (Map k a) #

liftShrink :: (a -> [a]) -> Map k a -> [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 #

(FromJSONKey k, Ord k) => FromJSON1 (Map k) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Map k a) #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Map k a] #

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 #

Ord k => Apply (Map k)

A 'Map k' is not Applicative, but it is an instance of Apply

Instance details

Defined in Data.Functor.Bind.Class

Methods

(<.>) :: Map k (a -> b) -> Map k a -> Map k b #

(.>) :: Map k a -> Map k b -> Map k b #

(<.) :: Map k a -> Map k b -> Map k a #

liftF2 :: (a -> b -> c) -> Map k a -> Map k b -> Map k c #

Ord k => Bind (Map k)

A 'Map k' is not a Monad, but it is an instance of Bind

Instance details

Defined in Data.Functor.Bind.Class

Methods

(>>-) :: Map k a -> (a -> Map k b) -> Map k b #

join :: Map k (Map k a) -> Map k a #

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) :: Type #

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 :: (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 #

(Ord k, Arbitrary k, Arbitrary v) => Arbitrary (Map k v) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Map k v) #

shrink :: Map k v -> [Map k v] #

(CoArbitrary k, CoArbitrary v) => CoArbitrary (Map k v) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

coarbitrary :: Map k v -> Gen b -> Gen b #

(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 #

(FromJSONKey k, Ord k, FromJSON v) => FromJSON (Map k v) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Map k v) #

parseJSONList :: Value -> Parser [Map k v] #

(NFData k, NFData a) => NFData (Map k a) 
Instance details

Defined in Data.Map.Internal

Methods

rnf :: Map k a -> () #

(Buildable' k, Buildable' v) => Buildable' (Map k v) 
Instance details

Defined in Fmt.Internal.Generic

Methods

build' :: Map k v -> Builder #

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) :: Type #

Methods

_Wrapped' :: Iso' (Map k a) (Unwrapped (Map k a)) #

One (Map k v) 
Instance details

Defined in Universum.Container.Class

Associated Types

type OneItem (Map k v) :: Type #

Methods

one :: OneItem (Map k v) -> Map k v #

Container (Map k v) 
Instance details

Defined in Universum.Container.Class

Associated Types

type Element (Map k v) :: Type #

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

ToPairs (Map k v) 
Instance details

Defined in Universum.Container.Class

Associated Types

type Key (Map k v) :: Type #

type Val (Map k v) :: Type #

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)] #

(Ord k, IsoCValue k, IsoValue v) => IsoValue (Map k v) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (Map k v) :: T Source #

Methods

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

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

(PolyCTypeHasDocC (k ': ([] :: [Type])), PolyTypeHasDocC (v ': ([] :: [Type])), Ord k) => TypeHasDoc (Map k v) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

IsComparable k => GetOpHs (Map k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

Associated Types

type GetOpKeyHs (Map k v) :: Type Source #

type GetOpValHs (Map k v) :: Type Source #

IsComparable k => UpdOpHs (Map k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

Associated Types

type UpdOpKeyHs (Map k v) :: Type Source #

type UpdOpParamsHs (Map k v) :: Type Source #

SizeOpHs (Map k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

IsComparable k => IterOpHs (Map k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

Associated Types

type IterOpElHs (Map k v) :: Type Source #

IsComparable k => MapOpHs (Map k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

Associated Types

type MapOpInpHs (Map k v) :: Type Source #

type MapOpResHs (Map k v) :: Type -> Type Source #

IsComparable k => MemOpHs (Map k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

Associated Types

type MemOpKeyHs (Map k v) :: Type 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

(key ~ key', value ~ value', IsComparable key) => StoreHasSubmap (Map key' value') name key value Source #

Map can be used as standalone key-value storage if very needed.

Instance details

Defined in Lorentz.StoreClass

Methods

storeSubmapOps :: StoreSubmapOps (Map key' value') name 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 OneItem (Map k v) 
Instance details

Defined in Universum.Container.Class

type OneItem (Map k v) = (k, v)
type Element (Map k v) 
Instance details

Defined in Universum.Container.Class

type Element (Map k v) = ElementDefault (Map k v)
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 ToT (Map k v) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT (Map k v) = TMap (ToCT 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 Source #

Constructors

BigMap 

Fields

Instances
(Eq k, Eq v) => Eq (BigMap k v) Source # 
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) Source # 
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) Source # 
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) Source # 
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) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Methods

def :: BigMap k v #

(Ord k, IsoCValue k, IsoValue v) => IsoValue (BigMap k v) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (BigMap k v) :: T Source #

Methods

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

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

(PolyCTypeHasDocC (k ': ([] :: [Type])), PolyTypeHasDocC (v ': ([] :: [Type])), Ord k) => TypeHasDoc (BigMap k v) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

IsComparable k => GetOpHs (BigMap k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

Associated Types

type GetOpKeyHs (BigMap k v) :: Type Source #

type GetOpValHs (BigMap k v) :: Type Source #

IsComparable k => UpdOpHs (BigMap k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

Associated Types

type UpdOpKeyHs (BigMap k v) :: Type Source #

type UpdOpParamsHs (BigMap k v) :: Type Source #

IsComparable k => MemOpHs (BigMap k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

Associated Types

type MemOpKeyHs (BigMap k v) :: Type Source #

(key ~ key', value ~ value', IsComparable key) => StoreHasSubmap (BigMap key' value') name key value Source #

BigMap can be used as standalone key-value storage, name of submap is not accounted in this case.

Instance details

Defined in Lorentz.StoreClass

Methods

storeSubmapOps :: StoreSubmapOps (BigMap key' value') name key value Source #

type ToT (BigMap k v) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT (BigMap k v) = TBigMap (ToCT 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

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
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 #

fail :: String -> 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 #

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

Arbitrary1 Maybe 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

liftArbitrary :: Gen a -> Gen (Maybe a) #

liftShrink :: (a -> [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 #

FromJSON1 Maybe 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Maybe a) #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Maybe a] #

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] #

MonadPlus Maybe

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mzero :: Maybe a #

mplus :: Maybe a -> 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 :: Type #

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 #

Apply Maybe 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(<.>) :: Maybe (a -> b) -> Maybe a -> Maybe b #

(.>) :: Maybe a -> Maybe b -> Maybe b #

(<.) :: Maybe a -> Maybe b -> Maybe a #

liftF2 :: (a -> b -> c) -> Maybe a -> Maybe b -> Maybe c #

InjValue Maybe 
Instance details

Defined in Named.Internal

Methods

injValue :: a -> Maybe a #

Bind Maybe 
Instance details

Defined in Data.Functor.Bind.Class

Methods

(>>-) :: Maybe a -> (a -> Maybe b) -> Maybe b #

join :: Maybe (Maybe 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 :: SApplicative f => Sing t1 -> Sing t2 -> Sing (Apply (Apply TraverseSym0 t1) t2) #

sSequenceA :: SApplicative f => Sing t1 -> Sing (Apply SequenceASym0 t1) #

sMapM :: SMonad m => Sing t1 -> Sing t2 -> Sing (Apply (Apply MapMSym0 t1) t2) #

sSequence :: 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 :: SMonoid m => Sing t1 -> Sing (Apply FoldSym0 t1) #

sFoldMap :: SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply FoldMapSym0 t1) t2) #

sFoldr :: Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply FoldrSym0 t1) t2) t3) #

sFoldr' :: Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply Foldr'Sym0 t1) t2) t3) #

sFoldl :: Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply FoldlSym0 t1) t2) t3) #

sFoldl' :: Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply Foldl'Sym0 t1) t2) t3) #

sFoldr1 :: Sing t1 -> Sing t2 -> Sing (Apply (Apply Foldr1Sym0 t1) t2) #

sFoldl1 :: Sing t1 -> Sing t2 -> Sing (Apply (Apply Foldl1Sym0 t1) t2) #

sToList :: Sing t1 -> Sing (Apply ToListSym0 t1) #

sNull :: Sing t1 -> Sing (Apply NullSym0 t1) #

sLength :: Sing t1 -> Sing (Apply LengthSym0 t1) #

sElem :: SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply ElemSym0 t1) t2) #

sMaximum :: SOrd a => Sing t1 -> Sing (Apply MaximumSym0 t1) #

sMinimum :: SOrd a => Sing t1 -> Sing (Apply MinimumSym0 t1) #

sSum :: SNum a => Sing t1 -> Sing (Apply SumSym0 t1) #

sProduct :: SNum a => Sing t1 -> Sing (Apply ProductSym0 t1) #

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 #

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 #

SFunctor Maybe 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

Methods

sFmap :: Sing t1 -> Sing t2 -> Sing (Apply (Apply FmapSym0 t1) t2) #

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

SApplicative Maybe 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

Methods

sPure :: Sing t -> Sing (Apply PureSym0 t) #

(%<*>) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (<*>@#@$) t1) t2) #

sLiftA2 :: Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply LiftA2Sym0 t1) t2) t3) #

(%*>) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (*>@#@$) t1) t2) #

(%<*) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (<*@#@$) t1) t2) #

SMonad Maybe 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

Methods

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

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

sReturn :: Sing t -> Sing (Apply ReturnSym0 t) #

sFail :: Sing t -> Sing (Apply FailSym0 t) #

SAlternative Maybe 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

Methods

sEmpty :: Sing EmptySym0 #

(%<|>) :: 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 :: Sing t1 -> Sing t2 -> Sing (Apply (Apply MplusSym0 t1) t2) #

LorentzFunctor Maybe Source # 
Instance details

Defined in Lorentz.Instr

Methods

lmap :: KnownValue b => ((a ': s) :-> (b ': s)) -> (Maybe a ': s) :-> (Maybe b ': s) Source #

MonadError () Maybe

Since: mtl-2.2.2

Instance details

Defined in Control.Monad.Error.Class

Methods

throwError :: () -> Maybe a #

catchError :: Maybe a -> (() -> Maybe a) -> Maybe a #

(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

() :=> (Functor Maybe) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Functor Maybe #

() :=> (Applicative Maybe) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Applicative Maybe #

() :=> (Alternative Maybe) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Alternative Maybe #

() :=> (MonadPlus Maybe) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- MonadPlus Maybe #

(Selector s, FromJSON a) => RecordFromJSON arity (S1 s (K1 i (Maybe a) :: Type -> Type)) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

recordParseJSON :: (ConName :* (TypeName :* (Options :* FromArgs arity a0))) -> Object -> Parser (S1 s (K1 i (Maybe a)) a0)

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 #

Data a => Data (Maybe a)

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

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

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

toConstr :: Maybe a -> Constr #

dataTypeOf :: Maybe a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Lift a => Lift (Maybe a) 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Maybe a -> Q Exp #

Testable prop => Testable (Maybe prop) 
Instance details

Defined in Test.QuickCheck.Property

Methods

property :: Maybe prop -> Property #

propertyForAllShrinkShow :: Gen a -> (a -> [a]) -> (a -> [String]) -> (a -> Maybe prop) -> Property #

Arbitrary a => Arbitrary (Maybe a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Maybe a) #

shrink :: Maybe a -> [Maybe a] #

CoArbitrary a => CoArbitrary (Maybe a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

coarbitrary :: Maybe a -> Gen b -> Gen b #

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

FromJSON a => FromJSON (Maybe a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

SingKind a => SingKind (Maybe a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type DemoteRep (Maybe a) :: Type

Methods

fromSing :: Sing a0 -> DemoteRep (Maybe a)

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 Fmt.Internal.Generic

Methods

build' :: Maybe a -> Builder #

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

(TypeError (DisallowInstance "Maybe") :: Constraint) => Container (Maybe a) 
Instance details

Defined in Universum.Container.Class

Associated Types

type Element (Maybe a) :: Type #

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

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

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 :: Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply ShowsPrecSym0 t1) t2) t3) #

sShow_ :: Sing t -> Sing (Apply Show_Sym0 t) #

sShowList :: 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

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

sSconcat :: 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 :: Sing t1 -> Sing t2 -> Sing (Apply (Apply CompareSym0 t1) t2) #

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

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

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

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

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

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

SEq a => SEq (Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Eq

Methods

(%==) :: Sing a0 -> Sing b -> Sing (a0 == b) #

(%/=) :: 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 #

IsOption (Maybe AntXMLPath) 
Instance details

Defined in Test.Tasty.Runners.AntXML

Pretty a => Pretty (Maybe a) 
Instance details

Defined in Text.PrettyPrint.Leijen.Text

Methods

pretty :: Maybe a -> Doc #

prettyList :: [Maybe a] -> Doc #

LookupField (Maybe a) 
Instance details

Defined in Data.Aeson.TH

Methods

lookupField :: (Value -> Parser (Maybe a)) -> String -> String -> Object -> Text -> Parser (Maybe a)

IsoValue a => IsoValue (Maybe a) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (Maybe a) :: T Source #

Methods

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

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

PolyTypeHasDocC (a ': ([] :: [Type])) => TypeHasDoc (Maybe a) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Generic1 Maybe 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Maybe :: k -> Type #

Methods

from1 :: Maybe a -> Rep1 Maybe a #

to1 :: Rep1 Maybe a -> Maybe a #

IsoHKD Maybe (a :: Type) 
Instance details

Defined in Data.Vinyl.XRec

Associated Types

type HKD Maybe a :: Type #

Methods

unHKD :: HKD Maybe a -> Maybe a #

toHKD :: Maybe a -> HKD Maybe a #

SingI (Nothing :: Maybe a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing Nothing

(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) #

Showtype (Nothing :: Maybe a) 
Instance details

Defined in Type.Showtype

Methods

showtype :: proxy Nothing -> String #

showtypesPrec :: Int -> proxy Nothing -> String -> String #

Each (Maybe a) (Maybe b) a b 
Instance details

Defined in Lens.Micro.Internal

Methods

each :: Traversal (Maybe a) (Maybe b) a b #

SingI a2 => SingI (Just a2 :: Maybe a1)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing (Just a2)

Showtype a2 => Showtype (Just a2 :: Maybe a1) 
Instance details

Defined in Type.Showtype

Methods

showtype :: proxy (Just a2) -> String #

showtypesPrec :: Int -> proxy (Just a2) -> String -> String #

SuppressUnusedWarnings (CatMaybesSym0 :: TyFun [Maybe a6989586621679494615] [a6989586621679494615] -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (ListToMaybeSym0 :: TyFun [a6989586621679494616] (Maybe a6989586621679494616) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (StripPrefixSym0 :: TyFun [a6989586621680065391] ([a6989586621680065391] ~> Maybe [a6989586621680065391]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (MaybeToListSym0 :: TyFun (Maybe a6989586621679494617) [a6989586621679494617] -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

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

Defined in Data.Singletons.Prelude.Maybe

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

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (FromJustSym0 :: TyFun (Maybe a6989586621679494619) a6989586621679494619 -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (TFHelper_6989586621679607603Sym0 :: TyFun (Maybe a6989586621679544228) (Maybe a6989586621679544228 ~> Maybe a6989586621679544228) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (MinInternalSym0 :: TyFun (Maybe a6989586621680441221) (MinInternal a6989586621680441221) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (MaxInternalSym0 :: TyFun (Maybe a6989586621680440542) (MaxInternal a6989586621680440542) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Compare_6989586621679390337Sym0 :: TyFun (Maybe a3530822107858468865) (Maybe a3530822107858468865 ~> Ordering) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (OptionSym0 :: TyFun (Maybe a6989586621679051008) (Option a6989586621679051008) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

SuppressUnusedWarnings (LastSym0 :: TyFun (Maybe a6989586621679072628) (Last a6989586621679072628) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

SuppressUnusedWarnings (FirstSym0 :: TyFun (Maybe a6989586621679072633) (First a6989586621679072633) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

SuppressUnusedWarnings (ShowsPrec_6989586621680280327Sym0 :: TyFun Nat (Maybe a3530822107858468865 ~> (Symbol ~> Symbol)) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings (Fail_6989586621679607510Sym0 :: TyFun Symbol (Maybe a6989586621679544179) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (FromMaybeSym0 :: TyFun a6989586621679494618 (Maybe a6989586621679494618 ~> a6989586621679494618) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (ElemIndexSym0 :: TyFun a6989586621679939175 ([a6989586621679939175] ~> Maybe Nat) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Pure_6989586621679607303Sym0 :: TyFun a6989586621679544150 (Maybe a6989586621679544150) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (Let6989586621679607599LSym0 :: TyFun k1 (Maybe k1) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (JustSym0 :: TyFun a3530822107858468865 (Maybe a3530822107858468865) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Instances

SuppressUnusedWarnings (GetOptionSym0 :: TyFun (Option a6989586621679051008) (Maybe a6989586621679051008) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

SuppressUnusedWarnings (GetFirstSym0 :: TyFun (First a6989586621679072633) (Maybe a6989586621679072633) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

SuppressUnusedWarnings (GetLastSym0 :: TyFun (Last a6989586621679072628) (Maybe a6989586621679072628) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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 (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 (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

SuppressUnusedWarnings (StripPrefixSym1 a6989586621680078101 :: TyFun [a6989586621680065391] (Maybe [a6989586621680065391]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (FindSym1 a6989586621679948733 :: TyFun [a6989586621679939176] (Maybe a6989586621679939176) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (FindIndexSym1 a6989586621679949093 :: TyFun [a6989586621679939173] (Maybe Nat) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (ElemIndexSym1 a6989586621679949101 :: TyFun [a6989586621679939175] (Maybe Nat) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (ShowsPrec_6989586621680280327Sym1 a6989586621680280324 a3530822107858468865 :: TyFun (Maybe a3530822107858468865) (Symbol ~> Symbol) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings (FromMaybeSym1 a6989586621679494810 :: TyFun (Maybe a6989586621679494618) a6989586621679494618 -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (TFHelper_6989586621679607603Sym1 a6989586621679607601 :: TyFun (Maybe a6989586621679544228) (Maybe a6989586621679544228) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (TFHelper_6989586621679607503Sym0 :: TyFun (Maybe a6989586621679544176) (Maybe b6989586621679544177 ~> Maybe b6989586621679544177) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (TFHelper_6989586621679607487Sym0 :: TyFun (Maybe a6989586621679544174) ((a6989586621679544174 ~> Maybe b6989586621679544175) ~> Maybe b6989586621679544175) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (TFHelper_6989586621679607345Sym0 :: TyFun (Maybe a6989586621679544156) (Maybe b6989586621679544157 ~> Maybe b6989586621679544157) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (Compare_6989586621679390337Sym1 a6989586621679390335 :: TyFun (Maybe a3530822107858468865) Ordering -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (TFHelper_6989586621679607315Sym0 :: TyFun (Maybe (a6989586621679544151 ~> b6989586621679544152)) (Maybe a6989586621679544151 ~> Maybe b6989586621679544152) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (Maybe_Sym0 :: TyFun b6989586621679493191 ((a6989586621679493192 ~> b6989586621679493191) ~> (Maybe a6989586621679493192 ~> b6989586621679493191)) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (LookupSym0 :: TyFun a6989586621679939154 ([(a6989586621679939154, b6989586621679939155)] ~> Maybe b6989586621679939155) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (TFHelper_6989586621679607174Sym0 :: TyFun a6989586621679544147 (Maybe b6989586621679544148 ~> Maybe a6989586621679544147) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (Let6989586621680442019NSym0 :: TyFun k (TyFun k1 (Maybe k1) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680442019MSym0 :: TyFun k1 (TyFun k (Maybe k1) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680441992NSym0 :: TyFun k (TyFun k1 (Maybe k1) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680441992MSym0 :: TyFun k1 (TyFun k (Maybe k1) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (MapMaybeSym0 :: TyFun (a6989586621679494613 ~> Maybe b6989586621679494614) ([a6989586621679494613] ~> [b6989586621679494614]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (UnfoldrSym0 :: TyFun (b6989586621679939232 ~> Maybe (a6989586621679939233, b6989586621679939232)) (b6989586621679939232 ~> [a6989586621679939233]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Fmap_6989586621679607154Sym0 :: TyFun (a6989586621679544145 ~> b6989586621679544146) (Maybe a6989586621679544145 ~> Maybe b6989586621679544146) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (FindSym0 :: TyFun (a6989586621680450110 ~> Bool) (t6989586621680450109 a6989586621680450110 ~> Maybe a6989586621680450110) -> 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) #

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 a6989586621679948515 b6989586621679939155 :: TyFun [(a6989586621679939154, b6989586621679939155)] (Maybe b6989586621679939155) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (TFHelper_6989586621679607503Sym1 a6989586621679607501 b6989586621679544177 :: TyFun (Maybe b6989586621679544177) (Maybe b6989586621679544177) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (TFHelper_6989586621679607345Sym1 a6989586621679607343 b6989586621679544157 :: TyFun (Maybe b6989586621679544157) (Maybe b6989586621679544157) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (TFHelper_6989586621679607315Sym1 a6989586621679607313 :: TyFun (Maybe a6989586621679544151) (Maybe b6989586621679544152) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (TFHelper_6989586621679607174Sym1 a6989586621679607172 b6989586621679544148 :: TyFun (Maybe b6989586621679544148) (Maybe a6989586621679544147) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (Fmap_6989586621679607154Sym1 a6989586621679607152 :: TyFun (Maybe a6989586621679544145) (Maybe b6989586621679544146) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (Let6989586621680442019NSym1 x6989586621680442017 :: TyFun k1 (Maybe k1) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680442019MSym1 x6989586621680442017 :: TyFun k (Maybe k1) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680441992NSym1 x6989586621680441990 :: TyFun k1 (Maybe k1) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680441992MSym1 x6989586621680441990 :: TyFun k (Maybe k1) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (FindSym1 a6989586621680450567 t6989586621680450109 :: TyFun (t6989586621680450109 a6989586621680450110) (Maybe a6989586621680450110) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Lambda_6989586621680338373Sym0 :: TyFun k (TyFun (k1 ~> Last a) (TyFun k1 (Maybe a) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

SuppressUnusedWarnings (Lambda_6989586621680338285Sym0 :: TyFun k (TyFun (k1 ~> First a) (TyFun k1 (Maybe a) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

SuppressUnusedWarnings (Traverse_6989586621680753875Sym0 :: TyFun (a6989586621680747714 ~> f6989586621680747713 b6989586621680747715) (Maybe a6989586621680747714 ~> f6989586621680747713 (Maybe b6989586621680747715)) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Traversable

SuppressUnusedWarnings (Maybe_Sym1 a6989586621679493209 a6989586621679493192 :: TyFun (a6989586621679493192 ~> b6989586621679493191) (Maybe a6989586621679493192 ~> b6989586621679493191) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (Let6989586621679494787RsSym0 :: TyFun (a6989586621679494613 ~> Maybe k1) (TyFun k (TyFun [a6989586621679494613] [k1] -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (TFHelper_6989586621679607487Sym1 a6989586621679607485 b6989586621679544175 :: TyFun (a6989586621679544174 ~> Maybe b6989586621679544175) (Maybe b6989586621679544175) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (LiftA2_6989586621679607331Sym0 :: TyFun (a6989586621679544153 ~> (b6989586621679544154 ~> c6989586621679544155)) (Maybe a6989586621679544153 ~> (Maybe b6989586621679544154 ~> Maybe c6989586621679544155)) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (Let6989586621680451044MfSym0 :: 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 (Let6989586621680451019MfSym0 :: TyFun (k3 ~> (k2 ~> k3)) (TyFun k (TyFun k3 (TyFun (Maybe k2) (Maybe k3) -> Type) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

(SEq a, SingI d) => SingI (LookupSym1 d b :: TyFun [(a, b)] (Maybe b) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (LookupSym1 d b) #

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

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing (FindSym1 d t) #

SingI d => SingI (Maybe_Sym1 d a :: TyFun (a ~> b) (Maybe a ~> b) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

Methods

sing :: Sing (Maybe_Sym1 d a) #

SuppressUnusedWarnings (Traverse_6989586621680753875Sym1 a6989586621680753873 :: TyFun (Maybe a6989586621680747714) (f6989586621680747713 (Maybe b6989586621680747715)) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Traversable

SuppressUnusedWarnings (Maybe_Sym2 a6989586621679493210 a6989586621679493209 :: TyFun (Maybe a6989586621679493192) b6989586621679493191 -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (LiftA2_6989586621679607331Sym1 a6989586621679607328 :: TyFun (Maybe a6989586621679544153) (Maybe b6989586621679544154 ~> Maybe c6989586621679544155) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (Let6989586621680451044MfSym1 f6989586621680451042 :: TyFun k (TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680451019MfSym1 f6989586621680451017 :: TyFun k (TyFun k3 (TyFun (Maybe k2) (Maybe k3) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Lambda_6989586621680338373Sym1 a6989586621680338371 :: TyFun (k1 ~> Last a) (TyFun k1 (Maybe a) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

SuppressUnusedWarnings (Lambda_6989586621680338285Sym1 a6989586621680338283 :: 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_6989586621679607331Sym2 a6989586621679607329 a6989586621679607328 :: TyFun (Maybe b6989586621679544154) (Maybe c6989586621679544155) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (Let6989586621680451044MfSym2 xs6989586621680451043 f6989586621680451042 :: TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680451019MfSym2 xs6989586621680451018 f6989586621680451017 :: TyFun k3 (TyFun (Maybe k2) (Maybe k3) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Lambda_6989586621680338373Sym2 k6989586621680338372 a6989586621680338371 :: TyFun k1 (Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

SuppressUnusedWarnings (Lambda_6989586621680338285Sym2 k6989586621680338284 a6989586621680338283 :: TyFun k1 (Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

SuppressUnusedWarnings (Let6989586621680451019MfSym3 a6989586621680451020 xs6989586621680451018 f6989586621680451017 :: TyFun (Maybe k2) (Maybe k3) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680451044MfSym3 a6989586621680451045 xs6989586621680451043 f6989586621680451042 :: TyFun k3 (Maybe k3) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

ToJSON a => ToJSON (NamedF Maybe a name) Source # 
Instance details

Defined in Util.Named

Methods

toJSON :: NamedF Maybe a name -> Value #

toEncoding :: NamedF Maybe a name -> Encoding #

toJSONList :: [NamedF Maybe a name] -> Value #

toEncodingList :: [NamedF Maybe a name] -> Encoding #

FromJSON a => FromJSON (NamedF Maybe a name) Source # 
Instance details

Defined in Util.Named

Methods

parseJSON :: Value -> Parser (NamedF Maybe a name) #

parseJSONList :: Value -> Parser [NamedF Maybe a name] #

Wrapped (NamedF Maybe a name) Source # 
Instance details

Defined in Util.Named

Associated Types

type Unwrapped (NamedF Maybe a name) :: Type #

Methods

_Wrapped' :: Iso' (NamedF Maybe a name) (Unwrapped (NamedF Maybe a name)) #

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

Defined in Michelson.Typed.Haskell.Value

Associated Types

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

Methods

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

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

type Failure Maybe 
Instance details

Defined in Basement.Monad

type Failure Maybe = ()
type Empty 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Empty = (Empty_6989586621679607591Sym0 :: Maybe a)
type Mzero 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Mzero = (Mzero_6989586621679544703Sym0 :: Maybe a)
type Product (arg :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Product (arg :: Maybe a) = Apply (Product_6989586621680451180Sym0 :: 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_6989586621680451167Sym0 :: 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_6989586621680451154Sym0 :: 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_6989586621680451141Sym0 :: 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_6989586621680451112Sym0 :: 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_6989586621680451090Sym0 :: 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_6989586621680451069Sym0 :: 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_6989586621680450886Sym0 :: 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_6989586621679607303Sym0 :: TyFun k1 (Maybe k1) -> Type) a
type Fail a2 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Fail a2 = Apply (Fail_6989586621679607510Sym0 :: TyFun Symbol (Maybe a1) -> Type) a2
type Return (arg :: a) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Return (arg :: a) = Apply (Return_6989586621679544685Sym0 :: 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_6989586621680747781Sym0 :: 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_6989586621680747756Sym0 :: 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_6989586621680451127Sym0 :: 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_6989586621680451059Sym0 :: 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_6989586621680451034Sym0 :: TyFun (a ~> (a ~> a)) (Maybe a ~> a) -> Type) arg1) arg2
type (a1 :: Maybe a6989586621679544228) <|> (a2 :: Maybe a6989586621679544228) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type (a1 :: Maybe a6989586621679544228) <|> (a2 :: Maybe a6989586621679544228) = Apply (Apply (TFHelper_6989586621679607603Sym0 :: TyFun (Maybe a6989586621679544228) (Maybe a6989586621679544228 ~> Maybe a6989586621679544228) -> Type) a1) a2
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_6989586621679544717Sym0 :: TyFun (Maybe a) (Maybe a ~> Maybe a) -> Type) arg1) arg2
type FoldMap (a1 :: a6989586621680450204 ~> k2) (a2 :: Maybe a6989586621680450204) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type FoldMap (a1 :: a6989586621680450204 ~> k2) (a2 :: Maybe a6989586621680450204) = Apply (Apply (FoldMap_6989586621680451198Sym0 :: TyFun (a6989586621680450204 ~> k2) (Maybe a6989586621680450204 ~> k2) -> Type) a1) a2
type (a1 :: k1) <$ (a2 :: Maybe b6989586621679544148) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type (a1 :: k1) <$ (a2 :: Maybe b6989586621679544148) = Apply (Apply (TFHelper_6989586621679607174Sym0 :: TyFun k1 (Maybe b6989586621679544148 ~> Maybe k1) -> Type) a1) a2
type Fmap (a1 :: a6989586621679544145 ~> b6989586621679544146) (a2 :: Maybe a6989586621679544145) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Fmap (a1 :: a6989586621679544145 ~> b6989586621679544146) (a2 :: Maybe a6989586621679544145) = Apply (Apply (Fmap_6989586621679607154Sym0 :: TyFun (a6989586621679544145 ~> b6989586621679544146) (Maybe a6989586621679544145 ~> Maybe b6989586621679544146) -> Type) a1) a2
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_6989586621679544641Sym0 :: TyFun (Maybe a) (Maybe b ~> Maybe a) -> Type) arg1) arg2
type (a1 :: Maybe a6989586621679544156) *> (a2 :: Maybe b6989586621679544157) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type (a1 :: Maybe a6989586621679544156) *> (a2 :: Maybe b6989586621679544157) = Apply (Apply (TFHelper_6989586621679607345Sym0 :: TyFun (Maybe a6989586621679544156) (Maybe b6989586621679544157 ~> Maybe b6989586621679544157) -> Type) a1) a2
type (a1 :: Maybe (a6989586621679544151 ~> b6989586621679544152)) <*> (a2 :: Maybe a6989586621679544151) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type (a1 :: Maybe (a6989586621679544151 ~> b6989586621679544152)) <*> (a2 :: Maybe a6989586621679544151) = Apply (Apply (TFHelper_6989586621679607315Sym0 :: TyFun (Maybe (a6989586621679544151 ~> b6989586621679544152)) (Maybe a6989586621679544151 ~> Maybe b6989586621679544152) -> Type) a1) a2
type (a1 :: Maybe a6989586621679544176) >> (a2 :: Maybe b6989586621679544177) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type (a1 :: Maybe a6989586621679544176) >> (a2 :: Maybe b6989586621679544177) = Apply (Apply (TFHelper_6989586621679607503Sym0 :: TyFun (Maybe a6989586621679544176) (Maybe b6989586621679544177 ~> Maybe b6989586621679544177) -> Type) a1) a2
type (a1 :: Maybe a6989586621679544174) >>= (a2 :: a6989586621679544174 ~> Maybe b6989586621679544175) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type (a1 :: Maybe a6989586621679544174) >>= (a2 :: a6989586621679544174 ~> Maybe b6989586621679544175) = Apply (Apply (TFHelper_6989586621679607487Sym0 :: TyFun (Maybe a6989586621679544174) ((a6989586621679544174 ~> Maybe b6989586621679544175) ~> Maybe b6989586621679544175) -> Type) a1) a2
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_6989586621680747771Sym0 :: TyFun (a ~> m b) (Maybe a ~> m (Maybe b)) -> Type) arg1) arg2
type Traverse (a1 :: a6989586621680747714 ~> f6989586621680747713 b6989586621680747715) (a2 :: Maybe a6989586621680747714) 
Instance details

Defined in Data.Singletons.Prelude.Traversable

type Traverse (a1 :: a6989586621680747714 ~> f6989586621680747713 b6989586621680747715) (a2 :: Maybe a6989586621680747714) = Apply (Apply (Traverse_6989586621680753875Sym0 :: TyFun (a6989586621680747714 ~> f6989586621680747713 b6989586621680747715) (Maybe a6989586621680747714 ~> f6989586621680747713 (Maybe b6989586621680747715)) -> Type) a1) a2
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'_6989586621680451008Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (Maybe a ~> b)) -> Type) arg1) arg2) arg3
type Foldl (a1 :: k2 ~> (a6989586621680450210 ~> k2)) (a2 :: k2) (a3 :: Maybe a6989586621680450210) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl (a1 :: k2 ~> (a6989586621680450210 ~> k2)) (a2 :: k2) (a3 :: Maybe a6989586621680450210) = Apply (Apply (Apply (Foldl_6989586621680451233Sym0 :: TyFun (k2 ~> (a6989586621680450210 ~> k2)) (k2 ~> (Maybe a6989586621680450210 ~> k2)) -> Type) a1) a2) a3
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'_6989586621680450953Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (Maybe a ~> b)) -> Type) arg1) arg2) arg3
type Foldr (a1 :: a6989586621680450205 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Maybe a6989586621680450205) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldr (a1 :: a6989586621680450205 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Maybe a6989586621680450205) = Apply (Apply (Apply (Foldr_6989586621680451215Sym0 :: TyFun (a6989586621680450205 ~> (k2 ~> k2)) (k2 ~> (Maybe a6989586621680450205 ~> k2)) -> Type) a1) a2) a3
type LiftA2 (a1 :: a6989586621679544153 ~> (b6989586621679544154 ~> c6989586621679544155)) (a2 :: Maybe a6989586621679544153) (a3 :: Maybe b6989586621679544154) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type LiftA2 (a1 :: a6989586621679544153 ~> (b6989586621679544154 ~> c6989586621679544155)) (a2 :: Maybe a6989586621679544153) (a3 :: Maybe b6989586621679544154) = Apply (Apply (Apply (LiftA2_6989586621679607331Sym0 :: TyFun (a6989586621679544153 ~> (b6989586621679544154 ~> c6989586621679544155)) (Maybe a6989586621679544153 ~> (Maybe b6989586621679544154 ~> Maybe c6989586621679544155)) -> Type) a1) a2) a3
type Apply (IsNothingSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679494823 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (IsNothingSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679494823 :: Maybe a) = IsNothing a6989586621679494823
type Apply (IsJustSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679494825 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (IsJustSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679494825 :: Maybe a) = IsJust a6989586621679494825
type Apply (FromJustSym0 :: TyFun (Maybe a) a -> Type) (a6989586621679494820 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (FromJustSym0 :: TyFun (Maybe a) a -> Type) (a6989586621679494820 :: Maybe a) = FromJust a6989586621679494820
type Apply (Compare_6989586621679390337Sym1 a6989586621679390335 :: TyFun (Maybe a) Ordering -> Type) (a6989586621679390336 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Compare_6989586621679390337Sym1 a6989586621679390335 :: TyFun (Maybe a) Ordering -> Type) (a6989586621679390336 :: Maybe a) = Compare_6989586621679390337 a6989586621679390335 a6989586621679390336
type Apply (FromMaybeSym1 a6989586621679494810 :: TyFun (Maybe a) a -> Type) (a6989586621679494811 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (FromMaybeSym1 a6989586621679494810 :: TyFun (Maybe a) a -> Type) (a6989586621679494811 :: Maybe a) = FromMaybe a6989586621679494810 a6989586621679494811
type Apply (Maybe_Sym2 a6989586621679493210 a6989586621679493209 :: TyFun (Maybe a) b -> Type) (a6989586621679493211 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (Maybe_Sym2 a6989586621679493210 a6989586621679493209 :: TyFun (Maybe a) b -> Type) (a6989586621679493211 :: Maybe a) = Maybe_ a6989586621679493210 a6989586621679493209 a6989586621679493211
type Rep (Maybe a)

Since: base-4.6.0.0

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)))
data Sing (b :: Maybe a) 
Instance details

Defined in GHC.Generics

data Sing (b :: Maybe a) where
type DemoteRep (Maybe a) 
Instance details

Defined in GHC.Generics

type DemoteRep (Maybe a) = Maybe (DemoteRep 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 Element (Maybe a) 
Instance details

Defined in Universum.Container.Class

type Element (Maybe a) = ElementDefault (Maybe a)
type Mempty 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Mempty = (Mempty_6989586621680328742Sym0 :: Maybe a)
data Sing (b :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (b :: Maybe a) where
type Demote (Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Demote (Maybe a) = Maybe (Demote a)
type ToT (Maybe a) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT (Maybe a) = TOption (ToT a)
type Rep1 Maybe

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Mconcat (arg :: [Maybe a]) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Mconcat (arg :: [Maybe a]) = Apply (Mconcat_6989586621680328692Sym0 :: 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__6989586621680262191Sym0 :: 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_6989586621679810463Sym0 :: 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_6989586621680328682Sym0 :: 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_6989586621680262202Sym0 :: 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_6989586621679810635Sym0 :: TyFun (Maybe a1) (Maybe a1 ~> Maybe a1) -> Type) a2) a3
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_6989586621679379696Sym0 :: 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_6989586621679379678Sym0 :: 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_6989586621679379660Sym0 :: 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_6989586621679379642Sym0 :: 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_6989586621679379624Sym0 :: 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_6989586621679379606Sym0 :: 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_6989586621679390337Sym0 :: 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_6989586621679364176 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_6989586621680280327Sym0 :: TyFun Nat (Maybe a1 ~> (Symbol ~> Symbol)) -> Type) a2) a3) a4
type Apply (Pure_6989586621679607303Sym0 :: TyFun a (Maybe a) -> Type) (a6989586621679607302 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (Pure_6989586621679607303Sym0 :: TyFun a (Maybe a) -> Type) (a6989586621679607302 :: a) = Pure_6989586621679607303 a6989586621679607302
type Apply (Fail_6989586621679607510Sym0 :: TyFun Symbol (Maybe a6989586621679544179) -> Type) (a6989586621679607509 :: Symbol) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (Fail_6989586621679607510Sym0 :: TyFun Symbol (Maybe a6989586621679544179) -> Type) (a6989586621679607509 :: Symbol) = (Fail_6989586621679607510 a6989586621679607509 :: Maybe a6989586621679544179)
type Apply (Let6989586621679607599LSym0 :: TyFun k1 (Maybe k1) -> Type) (wild_69895866216796067606989586621679607598 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (Let6989586621679607599LSym0 :: TyFun k1 (Maybe k1) -> Type) (wild_69895866216796067606989586621679607598 :: k1) = Let6989586621679607599L wild_69895866216796067606989586621679607598
type Apply (JustSym0 :: TyFun a (Maybe a) -> Type) (t6989586621679294054 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Apply (JustSym0 :: TyFun a (Maybe a) -> Type) (t6989586621679294054 :: a) = Just t6989586621679294054
type Apply (Let6989586621680441992MSym1 x6989586621680441990 :: TyFun k (Maybe k1) -> Type) (y6989586621680441991 :: k) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680441992MSym1 x6989586621680441990 :: TyFun k (Maybe k1) -> Type) (y6989586621680441991 :: k) = Let6989586621680441992M x6989586621680441990 y6989586621680441991
type Apply (Let6989586621680441992NSym1 x6989586621680441990 :: TyFun k1 (Maybe k1) -> Type) (y6989586621680441991 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680441992NSym1 x6989586621680441990 :: TyFun k1 (Maybe k1) -> Type) (y6989586621680441991 :: k1) = Let6989586621680441992N x6989586621680441990 y6989586621680441991
type Apply (Let6989586621680442019MSym1 x6989586621680442017 :: TyFun k (Maybe k1) -> Type) (y6989586621680442018 :: k) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680442019MSym1 x6989586621680442017 :: TyFun k (Maybe k1) -> Type) (y6989586621680442018 :: k) = Let6989586621680442019M x6989586621680442017 y6989586621680442018
type Apply (Let6989586621680442019NSym1 x6989586621680442017 :: TyFun k1 (Maybe k1) -> Type) (y6989586621680442018 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680442019NSym1 x6989586621680442017 :: TyFun k1 (Maybe k1) -> Type) (y6989586621680442018 :: k1) = Let6989586621680442019N x6989586621680442017 y6989586621680442018
type Apply (Lambda_6989586621680338285Sym2 k6989586621680338284 a6989586621680338283 :: TyFun k1 (Maybe a) -> Type) (t6989586621680338296 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (Lambda_6989586621680338285Sym2 k6989586621680338284 a6989586621680338283 :: TyFun k1 (Maybe a) -> Type) (t6989586621680338296 :: k1) = Lambda_6989586621680338285 k6989586621680338284 a6989586621680338283 t6989586621680338296
type Apply (Lambda_6989586621680338373Sym2 k6989586621680338372 a6989586621680338371 :: TyFun k1 (Maybe a) -> Type) (t6989586621680338384 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (Lambda_6989586621680338373Sym2 k6989586621680338372 a6989586621680338371 :: TyFun k1 (Maybe a) -> Type) (t6989586621680338384 :: k1) = Lambda_6989586621680338373 k6989586621680338372 a6989586621680338371 t6989586621680338384
type Apply (Let6989586621680451044MfSym3 a6989586621680451045 xs6989586621680451043 f6989586621680451042 :: TyFun k3 (Maybe k3) -> Type) (a6989586621680451046 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680451044MfSym3 a6989586621680451045 xs6989586621680451043 f6989586621680451042 :: TyFun k3 (Maybe k3) -> Type) (a6989586621680451046 :: k3) = Let6989586621680451044Mf a6989586621680451045 xs6989586621680451043 f6989586621680451042 a6989586621680451046
type Apply (CatMaybesSym0 :: TyFun [Maybe a] [a] -> Type) (a6989586621679494799 :: [Maybe a]) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (CatMaybesSym0 :: TyFun [Maybe a] [a] -> Type) (a6989586621679494799 :: [Maybe a]) = CatMaybes a6989586621679494799
type Apply (MaybeToListSym0 :: TyFun (Maybe a) [a] -> Type) (a6989586621679494807 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (MaybeToListSym0 :: TyFun (Maybe a) [a] -> Type) (a6989586621679494807 :: Maybe a) = MaybeToList a6989586621679494807
type Apply (ListToMaybeSym0 :: TyFun [a] (Maybe a) -> Type) (a6989586621679494804 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (ListToMaybeSym0 :: TyFun [a] (Maybe a) -> Type) (a6989586621679494804 :: [a]) = ListToMaybe a6989586621679494804
type Apply (GetOptionSym0 :: TyFun (Option a) (Maybe a) -> Type) (a6989586621679819644 :: Option a) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply (GetOptionSym0 :: TyFun (Option a) (Maybe a) -> Type) (a6989586621679819644 :: Option a) = GetOption a6989586621679819644
type Apply (GetFirstSym0 :: TyFun (First a) (Maybe a) -> Type) (a6989586621680332190 :: First a) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (GetFirstSym0 :: TyFun (First a) (Maybe a) -> Type) (a6989586621680332190 :: First a) = GetFirst a6989586621680332190
type Apply (GetLastSym0 :: TyFun (Last a) (Maybe a) -> Type) (a6989586621680332211 :: Last a) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (GetLastSym0 :: TyFun (Last a) (Maybe a) -> Type) (a6989586621680332211 :: Last a) = GetLast a6989586621680332211
type Apply (OptionSym0 :: TyFun (Maybe a) (Option a) -> Type) (t6989586621679819647 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply (OptionSym0 :: TyFun (Maybe a) (Option a) -> Type) (t6989586621679819647 :: Maybe a) = Option t6989586621679819647
type Apply (FirstSym0 :: TyFun (Maybe a) (First a) -> Type) (t6989586621680332193 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (FirstSym0 :: TyFun (Maybe a) (First a) -> Type) (t6989586621680332193 :: Maybe a) = First t6989586621680332193
type Apply (LastSym0 :: TyFun (Maybe a) (Last a) -> Type) (t6989586621680332214 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (LastSym0 :: TyFun (Maybe a) (Last a) -> Type) (t6989586621680332214 :: Maybe a) = Last t6989586621680332214
type Apply (MaxInternalSym0 :: TyFun (Maybe a) (MaxInternal a) -> Type) (t6989586621680441213 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MaxInternalSym0 :: TyFun (Maybe a) (MaxInternal a) -> Type) (t6989586621680441213 :: Maybe a) = MaxInternal t6989586621680441213
type Apply (MinInternalSym0 :: TyFun (Maybe a) (MinInternal a) -> Type) (t6989586621680441413 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MinInternalSym0 :: TyFun (Maybe a) (MinInternal a) -> Type) (t6989586621680441413 :: Maybe a) = MinInternal t6989586621680441413
type Apply (StripPrefixSym1 a6989586621680078101 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621680078102 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (StripPrefixSym1 a6989586621680078101 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621680078102 :: [a]) = StripPrefix a6989586621680078101 a6989586621680078102
type Apply (FindIndexSym1 a6989586621679949093 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679949094 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FindIndexSym1 a6989586621679949093 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679949094 :: [a]) = FindIndex a6989586621679949093 a6989586621679949094
type Apply (ElemIndexSym1 a6989586621679949101 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679949102 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ElemIndexSym1 a6989586621679949101 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679949102 :: [a]) = ElemIndex a6989586621679949101 a6989586621679949102
type Apply (FindSym1 a6989586621679948733 :: TyFun [a] (Maybe a) -> Type) (a6989586621679948734 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FindSym1 a6989586621679948733 :: TyFun [a] (Maybe a) -> Type) (a6989586621679948734 :: [a]) = Find a6989586621679948733 a6989586621679948734
type Apply (TFHelper_6989586621679607603Sym1 a6989586621679607601 :: TyFun (Maybe a) (Maybe a) -> Type) (a6989586621679607602 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621679607603Sym1 a6989586621679607601 :: TyFun (Maybe a) (Maybe a) -> Type) (a6989586621679607602 :: Maybe a) = TFHelper_6989586621679607603 a6989586621679607601 a6989586621679607602
type Apply (LookupSym1 a6989586621679948515 b :: TyFun [(a, b)] (Maybe b) -> Type) (a6989586621679948516 :: [(a, b)]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (LookupSym1 a6989586621679948515 b :: TyFun [(a, b)] (Maybe b) -> Type) (a6989586621679948516 :: [(a, b)]) = Lookup a6989586621679948515 a6989586621679948516
type Apply (Fmap_6989586621679607154Sym1 a6989586621679607152 :: TyFun (Maybe a) (Maybe b) -> Type) (a6989586621679607153 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (Fmap_6989586621679607154Sym1 a6989586621679607152 :: TyFun (Maybe a) (Maybe b) -> Type) (a6989586621679607153 :: Maybe a) = Fmap_6989586621679607154 a6989586621679607152 a6989586621679607153
type Apply (TFHelper_6989586621679607174Sym1 a6989586621679607172 b :: TyFun (Maybe b) (Maybe a) -> Type) (a6989586621679607173 :: Maybe b) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621679607174Sym1 a6989586621679607172 b :: TyFun (Maybe b) (Maybe a) -> Type) (a6989586621679607173 :: Maybe b) = TFHelper_6989586621679607174 a6989586621679607172 a6989586621679607173
type Apply (TFHelper_6989586621679607315Sym1 a6989586621679607313 :: TyFun (Maybe a) (Maybe b) -> Type) (a6989586621679607314 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621679607315Sym1 a6989586621679607313 :: TyFun (Maybe a) (Maybe b) -> Type) (a6989586621679607314 :: Maybe a) = TFHelper_6989586621679607315 a6989586621679607313 a6989586621679607314
type Apply (TFHelper_6989586621679607345Sym1 a6989586621679607343 b :: TyFun (Maybe b) (Maybe b) -> Type) (a6989586621679607344 :: Maybe b) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621679607345Sym1 a6989586621679607343 b :: TyFun (Maybe b) (Maybe b) -> Type) (a6989586621679607344 :: Maybe b) = TFHelper_6989586621679607345 a6989586621679607343 a6989586621679607344
type Apply (TFHelper_6989586621679607503Sym1 a6989586621679607501 b :: TyFun (Maybe b) (Maybe b) -> Type) (a6989586621679607502 :: Maybe b) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621679607503Sym1 a6989586621679607501 b :: TyFun (Maybe b) (Maybe b) -> Type) (a6989586621679607502 :: Maybe b) = TFHelper_6989586621679607503 a6989586621679607501 a6989586621679607502
type Apply (FindSym1 a6989586621680450567 t :: TyFun (t a) (Maybe a) -> Type) (a6989586621680450568 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FindSym1 a6989586621680450567 t :: TyFun (t a) (Maybe a) -> Type) (a6989586621680450568 :: t a) = Find a6989586621680450567 a6989586621680450568
type Apply (Traverse_6989586621680753875Sym1 a6989586621680753873 :: TyFun (Maybe a) (f (Maybe b)) -> Type) (a6989586621680753874 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Traversable

type Apply (Traverse_6989586621680753875Sym1 a6989586621680753873 :: TyFun (Maybe a) (f (Maybe b)) -> Type) (a6989586621680753874 :: Maybe a) = Traverse_6989586621680753875 a6989586621680753873 a6989586621680753874
type Apply (LiftA2_6989586621679607331Sym2 a6989586621679607329 a6989586621679607328 :: TyFun (Maybe b) (Maybe c) -> Type) (a6989586621679607330 :: Maybe b) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (LiftA2_6989586621679607331Sym2 a6989586621679607329 a6989586621679607328 :: TyFun (Maybe b) (Maybe c) -> Type) (a6989586621679607330 :: Maybe b) = LiftA2_6989586621679607331 a6989586621679607329 a6989586621679607328 a6989586621679607330
type Apply (Let6989586621680451019MfSym3 a6989586621680451020 xs6989586621680451018 f6989586621680451017 :: TyFun (Maybe k2) (Maybe k3) -> Type) (a6989586621680451021 :: Maybe k2) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680451019MfSym3 a6989586621680451020 xs6989586621680451018 f6989586621680451017 :: TyFun (Maybe k2) (Maybe k3) -> Type) (a6989586621680451021 :: Maybe k2) = Let6989586621680451019Mf a6989586621680451020 xs6989586621680451018 f6989586621680451017 a6989586621680451021
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 (Init (a2 ': ([] :: [a1])) :: Maybe [a1] -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (Init (a2 ': ([] :: [a1])) :: 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 (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 ': ([] :: [a1])) :: Maybe a1 -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (Last (a2 ': ([] :: [a1])) :: 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 (TFHelper_6989586621679607487Sym1 a6989586621679607485 b :: TyFun (a ~> Maybe b) (Maybe b) -> Type) (a6989586621679607486 :: a ~> Maybe b) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621679607487Sym1 a6989586621679607485 b :: TyFun (a ~> Maybe b) (Maybe b) -> Type) (a6989586621679607486 :: a ~> Maybe b) = TFHelper_6989586621679607487 a6989586621679607485 a6989586621679607486
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 (Find p (a2 ': as) :: Maybe a1 -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (Find p (a2 ': as) :: Maybe a1 -> Type) = If (Eval (p a2)) (Just a2) (Eval (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 (Map f (Just a3) :: Maybe a2 -> Type) 
Instance details

Defined in Fcf.Classes

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.Classes

type Eval (Map f (Nothing :: Maybe a) :: Maybe b -> Type) = (Nothing :: Maybe b)
type Apply (ElemIndexSym0 :: TyFun a6989586621679939175 ([a6989586621679939175] ~> Maybe Nat) -> Type) (a6989586621679949101 :: a6989586621679939175) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ElemIndexSym0 :: TyFun a6989586621679939175 ([a6989586621679939175] ~> Maybe Nat) -> Type) (a6989586621679949101 :: a6989586621679939175) = ElemIndexSym1 a6989586621679949101
type Apply (ShowsPrec_6989586621680280327Sym0 :: TyFun Nat (Maybe a3530822107858468865 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680280324 :: Nat) 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowsPrec_6989586621680280327Sym0 :: TyFun Nat (Maybe a3530822107858468865 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680280324 :: Nat) = (ShowsPrec_6989586621680280327Sym1 a6989586621680280324 a3530822107858468865 :: TyFun (Maybe a3530822107858468865) (Symbol ~> Symbol) -> Type)
type Apply (FromMaybeSym0 :: TyFun a6989586621679494618 (Maybe a6989586621679494618 ~> a6989586621679494618) -> Type) (a6989586621679494810 :: a6989586621679494618) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (FromMaybeSym0 :: TyFun a6989586621679494618 (Maybe a6989586621679494618 ~> a6989586621679494618) -> Type) (a6989586621679494810 :: a6989586621679494618) = FromMaybeSym1 a6989586621679494810
type Apply (Let6989586621680441992MSym0 :: TyFun k1 (TyFun k (Maybe k1) -> Type) -> Type) (x6989586621680441990 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680441992MSym0 :: TyFun k1 (TyFun k (Maybe k1) -> Type) -> Type) (x6989586621680441990 :: k1) = (Let6989586621680441992MSym1 x6989586621680441990 :: TyFun k (Maybe k1) -> Type)
type Apply (Let6989586621680441992NSym0 :: TyFun k (TyFun k1 (Maybe k1) -> Type) -> Type) (x6989586621680441990 :: k) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680441992NSym0 :: TyFun k (TyFun k1 (Maybe k1) -> Type) -> Type) (x6989586621680441990 :: k) = (Let6989586621680441992NSym1 x6989586621680441990 :: TyFun k1 (Maybe k1) -> Type)
type Apply (Let6989586621680442019MSym0 :: TyFun k1 (TyFun k (Maybe k1) -> Type) -> Type) (x6989586621680442017 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680442019MSym0 :: TyFun k1 (TyFun k (Maybe k1) -> Type) -> Type) (x6989586621680442017 :: k1) = (Let6989586621680442019MSym1 x6989586621680442017 :: TyFun k (Maybe k1) -> Type)
type Apply (Let6989586621680442019NSym0 :: TyFun k (TyFun k1 (Maybe k1) -> Type) -> Type) (x6989586621680442017 :: k) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680442019NSym0 :: TyFun k (TyFun k1 (Maybe k1) -> Type) -> Type) (x6989586621680442017 :: k) = (Let6989586621680442019NSym1 x6989586621680442017 :: TyFun k1 (Maybe k1) -> Type)
type Apply (LookupSym0 :: TyFun a6989586621679939154 ([(a6989586621679939154, b6989586621679939155)] ~> Maybe b6989586621679939155) -> Type) (a6989586621679948515 :: a6989586621679939154) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (LookupSym0 :: TyFun a6989586621679939154 ([(a6989586621679939154, b6989586621679939155)] ~> Maybe b6989586621679939155) -> Type) (a6989586621679948515 :: a6989586621679939154) = (LookupSym1 a6989586621679948515 b6989586621679939155 :: TyFun [(a6989586621679939154, b6989586621679939155)] (Maybe b6989586621679939155) -> Type)
type Apply (TFHelper_6989586621679607174Sym0 :: TyFun a6989586621679544147 (Maybe b6989586621679544148 ~> Maybe a6989586621679544147) -> Type) (a6989586621679607172 :: a6989586621679544147) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621679607174Sym0 :: TyFun a6989586621679544147 (Maybe b6989586621679544148 ~> Maybe a6989586621679544147) -> Type) (a6989586621679607172 :: a6989586621679544147) = (TFHelper_6989586621679607174Sym1 a6989586621679607172 b6989586621679544148 :: TyFun (Maybe b6989586621679544148) (Maybe a6989586621679544147) -> Type)
type Apply (Maybe_Sym0 :: TyFun b6989586621679493191 ((a6989586621679493192 ~> b6989586621679493191) ~> (Maybe a6989586621679493192 ~> b6989586621679493191)) -> Type) (a6989586621679493209 :: b6989586621679493191) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (Maybe_Sym0 :: TyFun b6989586621679493191 ((a6989586621679493192 ~> b6989586621679493191) ~> (Maybe a6989586621679493192 ~> b6989586621679493191)) -> Type) (a6989586621679493209 :: b6989586621679493191) = (Maybe_Sym1 a6989586621679493209 a6989586621679493192 :: TyFun (a6989586621679493192 ~> b6989586621679493191) (Maybe a6989586621679493192 ~> b6989586621679493191) -> Type)
type Apply (Lambda_6989586621680338285Sym0 :: TyFun k (TyFun (k1 ~> First a) (TyFun k1 (Maybe a) -> Type) -> Type) -> Type) (a6989586621680338283 :: k) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (Lambda_6989586621680338285Sym0 :: TyFun k (TyFun (k1 ~> First a) (TyFun k1 (Maybe a) -> Type) -> Type) -> Type) (a6989586621680338283 :: k) = (Lambda_6989586621680338285Sym1 a6989586621680338283 :: TyFun (k1 ~> First a) (TyFun k1 (Maybe a) -> Type) -> Type)
type Apply (Lambda_6989586621680338373Sym0 :: TyFun k (TyFun (k1 ~> Last a) (TyFun k1 (Maybe a) -> Type) -> Type) -> Type) (a6989586621680338371 :: k) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (Lambda_6989586621680338373Sym0 :: TyFun k (TyFun (k1 ~> Last a) (TyFun k1 (Maybe a) -> Type) -> Type) -> Type) (a6989586621680338371 :: k) = (Lambda_6989586621680338373Sym1 a6989586621680338371 :: TyFun (k1 ~> Last a) (TyFun k1 (Maybe a) -> Type) -> Type)
type Apply (Let6989586621680451044MfSym1 f6989586621680451042 :: TyFun k (TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) -> Type) (xs6989586621680451043 :: k) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680451044MfSym1 f6989586621680451042 :: TyFun k (TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) -> Type) (xs6989586621680451043 :: k) = Let6989586621680451044MfSym2 f6989586621680451042 xs6989586621680451043
type Apply (Let6989586621680451019MfSym1 f6989586621680451017 :: TyFun k (TyFun k3 (TyFun (Maybe k2) (Maybe k3) -> Type) -> Type) -> Type) (xs6989586621680451018 :: k) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680451019MfSym1 f6989586621680451017 :: TyFun k (TyFun k3 (TyFun (Maybe k2) (Maybe k3) -> Type) -> Type) -> Type) (xs6989586621680451018 :: k) = Let6989586621680451019MfSym2 f6989586621680451017 xs6989586621680451018
type Apply (Let6989586621680451019MfSym2 xs6989586621680451018 f6989586621680451017 :: TyFun k3 (TyFun (Maybe k2) (Maybe k3) -> Type) -> Type) (a6989586621680451020 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680451019MfSym2 xs6989586621680451018 f6989586621680451017 :: TyFun k3 (TyFun (Maybe k2) (Maybe k3) -> Type) -> Type) (a6989586621680451020 :: k3) = Let6989586621680451019MfSym3 xs6989586621680451018 f6989586621680451017 a6989586621680451020
type Apply (StripPrefixSym0 :: TyFun [a6989586621680065391] ([a6989586621680065391] ~> Maybe [a6989586621680065391]) -> Type) (a6989586621680078101 :: [a6989586621680065391]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (StripPrefixSym0 :: TyFun [a6989586621680065391] ([a6989586621680065391] ~> Maybe [a6989586621680065391]) -> Type) (a6989586621680078101 :: [a6989586621680065391]) = StripPrefixSym1 a6989586621680078101
type Apply (TFHelper_6989586621679607603Sym0 :: TyFun (Maybe a6989586621679544228) (Maybe a6989586621679544228 ~> Maybe a6989586621679544228) -> Type) (a6989586621679607601 :: Maybe a6989586621679544228) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621679607603Sym0 :: TyFun (Maybe a6989586621679544228) (Maybe a6989586621679544228 ~> Maybe a6989586621679544228) -> Type) (a6989586621679607601 :: Maybe a6989586621679544228) = TFHelper_6989586621679607603Sym1 a6989586621679607601
type Apply (Compare_6989586621679390337Sym0 :: TyFun (Maybe a3530822107858468865) (Maybe a3530822107858468865 ~> Ordering) -> Type) (a6989586621679390335 :: Maybe a3530822107858468865) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Compare_6989586621679390337Sym0 :: TyFun (Maybe a3530822107858468865) (Maybe a3530822107858468865 ~> Ordering) -> Type) (a6989586621679390335 :: Maybe a3530822107858468865) = Compare_6989586621679390337Sym1 a6989586621679390335
type Apply (TFHelper_6989586621679607315Sym0 :: TyFun (Maybe (a6989586621679544151 ~> b6989586621679544152)) (Maybe a6989586621679544151 ~> Maybe b6989586621679544152) -> Type) (a6989586621679607313 :: Maybe (a6989586621679544151 ~> b6989586621679544152)) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621679607315Sym0 :: TyFun (Maybe (a6989586621679544151 ~> b6989586621679544152)) (Maybe a6989586621679544151 ~> Maybe b6989586621679544152) -> Type) (a6989586621679607313 :: Maybe (a6989586621679544151 ~> b6989586621679544152)) = TFHelper_6989586621679607315Sym1 a6989586621679607313
type Apply (TFHelper_6989586621679607345Sym0 :: TyFun (Maybe a6989586621679544156) (Maybe b6989586621679544157 ~> Maybe b6989586621679544157) -> Type) (a6989586621679607343 :: Maybe a6989586621679544156) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621679607345Sym0 :: TyFun (Maybe a6989586621679544156) (Maybe b6989586621679544157 ~> Maybe b6989586621679544157) -> Type) (a6989586621679607343 :: Maybe a6989586621679544156) = (TFHelper_6989586621679607345Sym1 a6989586621679607343 b6989586621679544157 :: TyFun (Maybe b6989586621679544157) (Maybe b6989586621679544157) -> Type)
type Apply (TFHelper_6989586621679607503Sym0 :: TyFun (Maybe a6989586621679544176) (Maybe b6989586621679544177 ~> Maybe b6989586621679544177) -> Type) (a6989586621679607501 :: Maybe a6989586621679544176) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621679607503Sym0 :: TyFun (Maybe a6989586621679544176) (Maybe b6989586621679544177 ~> Maybe b6989586621679544177) -> Type) (a6989586621679607501 :: Maybe a6989586621679544176) = (TFHelper_6989586621679607503Sym1 a6989586621679607501 b6989586621679544177 :: TyFun (Maybe b6989586621679544177) (Maybe b6989586621679544177) -> Type)
type Apply (ShowsPrec_6989586621680280327Sym1 a6989586621680280324 a3530822107858468865 :: TyFun (Maybe a3530822107858468865) (Symbol ~> Symbol) -> Type) (a6989586621680280325 :: Maybe a3530822107858468865) 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowsPrec_6989586621680280327Sym1 a6989586621680280324 a3530822107858468865 :: TyFun (Maybe a3530822107858468865) (Symbol ~> Symbol) -> Type) (a6989586621680280325 :: Maybe a3530822107858468865) = ShowsPrec_6989586621680280327Sym2 a6989586621680280324 a6989586621680280325
type Apply (TFHelper_6989586621679607487Sym0 :: TyFun (Maybe a6989586621679544174) ((a6989586621679544174 ~> Maybe b6989586621679544175) ~> Maybe b6989586621679544175) -> Type) (a6989586621679607485 :: Maybe a6989586621679544174) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621679607487Sym0 :: TyFun (Maybe a6989586621679544174) ((a6989586621679544174 ~> Maybe b6989586621679544175) ~> Maybe b6989586621679544175) -> Type) (a6989586621679607485 :: Maybe a6989586621679544174) = (TFHelper_6989586621679607487Sym1 a6989586621679607485 b6989586621679544175 :: TyFun (a6989586621679544174 ~> Maybe b6989586621679544175) (Maybe b6989586621679544175) -> Type)
type Apply (LiftA2_6989586621679607331Sym1 a6989586621679607328 :: TyFun (Maybe a6989586621679544153) (Maybe b6989586621679544154 ~> Maybe c6989586621679544155) -> Type) (a6989586621679607329 :: Maybe a6989586621679544153) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (LiftA2_6989586621679607331Sym1 a6989586621679607328 :: TyFun (Maybe a6989586621679544153) (Maybe b6989586621679544154 ~> Maybe c6989586621679544155) -> Type) (a6989586621679607329 :: Maybe a6989586621679544153) = LiftA2_6989586621679607331Sym2 a6989586621679607328 a6989586621679607329
type Apply (Let6989586621680451044MfSym2 xs6989586621680451043 f6989586621680451042 :: TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) (a6989586621680451045 :: Maybe k2) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680451044MfSym2 xs6989586621680451043 f6989586621680451042 :: TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) (a6989586621680451045 :: Maybe k2) = Let6989586621680451044MfSym3 xs6989586621680451043 f6989586621680451042 a6989586621680451045
type Apply (FindSym0 :: TyFun (a6989586621679939176 ~> Bool) ([a6989586621679939176] ~> Maybe a6989586621679939176) -> Type) (a6989586621679948733 :: a6989586621679939176 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FindSym0 :: TyFun (a6989586621679939176 ~> Bool) ([a6989586621679939176] ~> Maybe a6989586621679939176) -> Type) (a6989586621679948733 :: a6989586621679939176 ~> Bool) = FindSym1 a6989586621679948733
type Apply (FindIndexSym0 :: TyFun (a6989586621679939173 ~> Bool) ([a6989586621679939173] ~> Maybe Nat) -> Type) (a6989586621679949093 :: a6989586621679939173 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FindIndexSym0 :: TyFun (a6989586621679939173 ~> Bool) ([a6989586621679939173] ~> Maybe Nat) -> Type) (a6989586621679949093 :: a6989586621679939173 ~> Bool) = FindIndexSym1 a6989586621679949093
type Apply (MapMaybeSym0 :: TyFun (a6989586621679494613 ~> Maybe b6989586621679494614) ([a6989586621679494613] ~> [b6989586621679494614]) -> Type) (a6989586621679494780 :: a6989586621679494613 ~> Maybe b6989586621679494614) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (MapMaybeSym0 :: TyFun (a6989586621679494613 ~> Maybe b6989586621679494614) ([a6989586621679494613] ~> [b6989586621679494614]) -> Type) (a6989586621679494780 :: a6989586621679494613 ~> Maybe b6989586621679494614) = MapMaybeSym1 a6989586621679494780
type Apply (Fmap_6989586621679607154Sym0 :: TyFun (a6989586621679544145 ~> b6989586621679544146) (Maybe a6989586621679544145 ~> Maybe b6989586621679544146) -> Type) (a6989586621679607152 :: a6989586621679544145 ~> b6989586621679544146) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (Fmap_6989586621679607154Sym0 :: TyFun (a6989586621679544145 ~> b6989586621679544146) (Maybe a6989586621679544145 ~> Maybe b6989586621679544146) -> Type) (a6989586621679607152 :: a6989586621679544145 ~> b6989586621679544146) = Fmap_6989586621679607154Sym1 a6989586621679607152
type Apply (UnfoldrSym0 :: TyFun (b6989586621679939232 ~> Maybe (a6989586621679939233, b6989586621679939232)) (b6989586621679939232 ~> [a6989586621679939233]) -> Type) (a6989586621679949166 :: b6989586621679939232 ~> Maybe (a6989586621679939233, b6989586621679939232)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (UnfoldrSym0 :: TyFun (b6989586621679939232 ~> Maybe (a6989586621679939233, b6989586621679939232)) (b6989586621679939232 ~> [a6989586621679939233]) -> Type) (a6989586621679949166 :: b6989586621679939232 ~> Maybe (a6989586621679939233, b6989586621679939232)) = UnfoldrSym1 a6989586621679949166
type Apply (FindSym0 :: TyFun (a6989586621680450110 ~> Bool) (t6989586621680450109 a6989586621680450110 ~> Maybe a6989586621680450110) -> Type) (a6989586621680450567 :: a6989586621680450110 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FindSym0 :: TyFun (a6989586621680450110 ~> Bool) (t6989586621680450109 a6989586621680450110 ~> Maybe a6989586621680450110) -> Type) (a6989586621680450567 :: a6989586621680450110 ~> Bool) = (FindSym1 a6989586621680450567 t6989586621680450109 :: TyFun (t6989586621680450109 a6989586621680450110) (Maybe a6989586621680450110) -> Type)
type Apply (Let6989586621679494787RsSym0 :: TyFun (a6989586621679494613 ~> Maybe k1) (TyFun k (TyFun [a6989586621679494613] [k1] -> Type) -> Type) -> Type) (f6989586621679494784 :: a6989586621679494613 ~> Maybe k1) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (Let6989586621679494787RsSym0 :: TyFun (a6989586621679494613 ~> Maybe k1) (TyFun k (TyFun [a6989586621679494613] [k1] -> Type) -> Type) -> Type) (f6989586621679494784 :: a6989586621679494613 ~> Maybe k1) = (Let6989586621679494787RsSym1 f6989586621679494784 :: TyFun k (TyFun [a6989586621679494613] [k1] -> Type) -> Type)
type Apply (Let6989586621680451019MfSym0 :: TyFun (k3 ~> (k2 ~> k3)) (TyFun k (TyFun k3 (TyFun (Maybe k2) (Maybe k3) -> Type) -> Type) -> Type) -> Type) (f6989586621680451017 :: k3 ~> (k2 ~> k3)) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680451019MfSym0 :: TyFun (k3 ~> (k2 ~> k3)) (TyFun k (TyFun k3 (TyFun (Maybe k2) (Maybe k3) -> Type) -> Type) -> Type) -> Type) (f6989586621680451017 :: k3 ~> (k2 ~> k3)) = (Let6989586621680451019MfSym1 f6989586621680451017 :: TyFun k (TyFun k3 (TyFun (Maybe k2) (Maybe k3) -> Type) -> Type) -> Type)
type Apply (Let6989586621680451044MfSym0 :: TyFun (k2 ~> (k3 ~> k3)) (TyFun k (TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) -> Type) -> Type) (f6989586621680451042 :: k2 ~> (k3 ~> k3)) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680451044MfSym0 :: TyFun (k2 ~> (k3 ~> k3)) (TyFun k (TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) -> Type) -> Type) (f6989586621680451042 :: k2 ~> (k3 ~> k3)) = (Let6989586621680451044MfSym1 f6989586621680451042 :: TyFun k (TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) -> Type)
type Apply (Traverse_6989586621680753875Sym0 :: TyFun (a6989586621680747714 ~> f6989586621680747713 b6989586621680747715) (Maybe a6989586621680747714 ~> f6989586621680747713 (Maybe b6989586621680747715)) -> Type) (a6989586621680753873 :: a6989586621680747714 ~> f6989586621680747713 b6989586621680747715) 
Instance details

Defined in Data.Singletons.Prelude.Traversable

type Apply (Traverse_6989586621680753875Sym0 :: TyFun (a6989586621680747714 ~> f6989586621680747713 b6989586621680747715) (Maybe a6989586621680747714 ~> f6989586621680747713 (Maybe b6989586621680747715)) -> Type) (a6989586621680753873 :: a6989586621680747714 ~> f6989586621680747713 b6989586621680747715) = Traverse_6989586621680753875Sym1 a6989586621680753873
type Apply (Maybe_Sym1 a6989586621679493209 a6989586621679493192 :: TyFun (a6989586621679493192 ~> b6989586621679493191) (Maybe a6989586621679493192 ~> b6989586621679493191) -> Type) (a6989586621679493210 :: a6989586621679493192 ~> b6989586621679493191) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (Maybe_Sym1 a6989586621679493209 a6989586621679493192 :: TyFun (a6989586621679493192 ~> b6989586621679493191) (Maybe a6989586621679493192 ~> b6989586621679493191) -> Type) (a6989586621679493210 :: a6989586621679493192 ~> b6989586621679493191) = Maybe_Sym2 a6989586621679493209 a6989586621679493210
type Apply (LiftA2_6989586621679607331Sym0 :: TyFun (a6989586621679544153 ~> (b6989586621679544154 ~> c6989586621679544155)) (Maybe a6989586621679544153 ~> (Maybe b6989586621679544154 ~> Maybe c6989586621679544155)) -> Type) (a6989586621679607328 :: a6989586621679544153 ~> (b6989586621679544154 ~> c6989586621679544155)) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (LiftA2_6989586621679607331Sym0 :: TyFun (a6989586621679544153 ~> (b6989586621679544154 ~> c6989586621679544155)) (Maybe a6989586621679544153 ~> (Maybe b6989586621679544154 ~> Maybe c6989586621679544155)) -> Type) (a6989586621679607328 :: a6989586621679544153 ~> (b6989586621679544154 ~> c6989586621679544155)) = LiftA2_6989586621679607331Sym1 a6989586621679607328
type Apply (Lambda_6989586621680338285Sym1 a6989586621680338283 :: TyFun (k1 ~> First a) (TyFun k1 (Maybe a) -> Type) -> Type) (k6989586621680338284 :: k1 ~> First a) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (Lambda_6989586621680338285Sym1 a6989586621680338283 :: TyFun (k1 ~> First a) (TyFun k1 (Maybe a) -> Type) -> Type) (k6989586621680338284 :: k1 ~> First a) = Lambda_6989586621680338285Sym2 a6989586621680338283 k6989586621680338284
type Apply (Lambda_6989586621680338373Sym1 a6989586621680338371 :: TyFun (k1 ~> Last a) (TyFun k1 (Maybe a) -> Type) -> Type) (k6989586621680338372 :: k1 ~> Last a) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (Lambda_6989586621680338373Sym1 a6989586621680338371 :: TyFun (k1 ~> Last a) (TyFun k1 (Maybe a) -> Type) -> Type) (k6989586621680338372 :: k1 ~> Last a) = Lambda_6989586621680338373Sym2 a6989586621680338371 k6989586621680338372
type Unwrapped (NamedF Maybe a name) Source # 
Instance details

Defined in Util.Named

type Unwrapped (NamedF Maybe a name) = Maybe a
type ToT (NamedF Maybe a name) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT (NamedF Maybe a name) = ToT (Maybe a)

type List = [] Source #

data ContractRef (arg :: Type) Source #

Since Contract name is used to designate contract code, lets call analogy of TContract type as follows.

Instances
cp ~ cp' => FromContractRef cp (ContractRef cp') Source # 
Instance details

Defined in Lorentz.Value

cp ~ cp' => ToContractRef cp (ContractRef cp') Source # 
Instance details

Defined in Lorentz.Value

Eq (ContractRef arg) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Methods

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

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

Show (ContractRef arg) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Methods

showsPrec :: Int -> ContractRef arg -> ShowS #

show :: ContractRef arg -> String #

showList :: [ContractRef arg] -> ShowS #

Buildable (ContractRef arg) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Methods

build :: ContractRef arg -> Builder #

IsoValue (ContractRef arg) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (ContractRef arg) :: T Source #

PolyTypeHasDocC (cp ': ([] :: [Type])) => TypeHasDoc (ContractRef cp) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Doc

ToAddress (ContractRef cp) Source # 
Instance details

Defined in Lorentz.Value

type ToT (ContractRef arg) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT (ContractRef arg) = TContract (ToT arg)

newtype FutureContract p Source #

Address associated with the contract of given type.

Places where ContractAddr can appear are now severely limited, this type gives you type-safety of ContractAddr but still can be used everywhere.

This may be refer to specific entrypoint of the contract, in such case type parameter p stands for argument of that entrypoint like in ContractAddr.

You still cannot be sure that the referred contract exists though.

Instances
cp ~ cp' => FromContractRef cp (FutureContract cp') Source # 
Instance details

Defined in Lorentz.Value

(NiceParameter cp, cp ~ cp') => ToContractRef cp (FutureContract cp') Source # 
Instance details

Defined in Lorentz.Value

Generic (FutureContract p) Source # 
Instance details

Defined in Lorentz.Value

Associated Types

type Rep (FutureContract p) :: Type -> Type #

IsoValue (FutureContract p) Source # 
Instance details

Defined in Lorentz.Value

Associated Types

type ToT (FutureContract p) :: T Source #

ToAddress (FutureContract cp) Source # 
Instance details

Defined in Lorentz.Value

type Rep (FutureContract p) Source # 
Instance details

Defined in Lorentz.Value

type Rep (FutureContract p) = D1 (MetaData "FutureContract" "Lorentz.Value" "morley-0.5.0-GrlgowF8t30F9AnUlsv4ov" True) (C1 (MetaCons "FutureContract" PrefixI True) (S1 (MetaSel (Just "futureContractAddress") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 EpAddress)))
type ToT (FutureContract p) Source # 
Instance details

Defined in Lorentz.Value

type EntryPointCall param arg = EntryPointCallT (ToT param) (ToT arg) Source #

Constructors

toMutez :: Word32 -> Mutez Source #

Safely create Mutez.

This is recommended way to create Mutez from a numeric literal; you can't construct all valid Mutez values using this function but for small values it works neat.

Warnings displayed when trying to construct invalid Natural or Word literal are hardcoded for these types in GHC implementation, so we can only exploit these existing rules.

mt :: QuasiQuoter Source #

QuasyQuoter for constructing Michelson strings.

Validity of result will be checked at compile time. Note:

  • slash must be escaped
  • newline character must appear as '\n'
  • use quotes as is
  • other special characters are not allowed.

timestampQuote :: QuasiQuoter Source #

Quote a value of type Timestamp in yyyy-mm-ddThh:mm:ss[.sss]Z format.

>>> formatTimestamp [timestampQuote| 2019-02-21T16:54:12.2344523Z |]
"2019-02-21T16:54:12Z"

Inspired by 'time-quote' library.

Conversions

coerceContractRef :: ToT a ~ ToT b => ContractRef a -> ContractRef b Source #

Replace type argument of ContractAddr with isomorphic one.

embodyFutureContract :: forall arg. (NiceParameter arg, HasCallStack) => FutureContract arg -> ContractRef arg Source #

Turn future contract into actual contract.

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
ToAddress Address Source # 
Instance details

Defined in Lorentz.Value

ToAddress EpAddress Source # 
Instance details

Defined in Lorentz.Value

ToAddress (ContractRef cp) Source # 
Instance details

Defined in Lorentz.Value

ToAddress (FutureContract cp) Source # 
Instance details

Defined in Lorentz.Value

class ToContractRef (cp :: Type) (contract :: Type) where Source #

Convert something to ContractRef in Haskell world.

Methods

toContractRef :: HasCallStack => contract -> ContractRef cp Source #

Instances
NiceParameter cp => ToContractRef cp Address Source #

Make contract ref calling the default entrypoint.

Instance details

Defined in Lorentz.Value

NiceParameter cp => ToContractRef cp EpAddress Source # 
Instance details

Defined in Lorentz.Value

cp ~ cp' => ToContractRef cp (ContractRef cp') Source # 
Instance details

Defined in Lorentz.Value

(NiceParameter cp, cp ~ cp') => ToContractRef cp (FutureContract cp') Source # 
Instance details

Defined in Lorentz.Value

class FromContractRef (cp :: Type) (contract :: Type) where Source #

Convert something from ContractAddr in Haskell world.

Methods

fromContractAddr :: ContractRef cp -> contract Source #

Instances
FromContractRef cp Address Source # 
Instance details

Defined in Lorentz.Value

FromContractRef cp EpAddress Source # 
Instance details

Defined in Lorentz.Value

cp ~ cp' => FromContractRef cp (ContractRef cp') Source # 
Instance details

Defined in Lorentz.Value

cp ~ cp' => FromContractRef cp (FutureContract cp') Source # 
Instance details

Defined in Lorentz.Value

convertContractRef :: forall cp contract2 contract1. (ToContractRef cp contract1, FromContractRef cp contract2) => contract1 -> contract2 Source #

Misc

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
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 Natural Source # 
Instance details

Defined in Util.Instances

Methods

def :: Natural #

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 InstrCallStack Source # 
Instance details

Defined in Michelson.ErrorPos

Methods

def :: InstrCallStack #

Default SrcPos Source # 
Instance details

Defined in Michelson.ErrorPos

Methods

def :: SrcPos #

Default Pos Source # 
Instance details

Defined in Michelson.ErrorPos

Methods

def :: Pos #

Default EpName Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Methods

def :: EpName #

Default OptimizerConf Source # 
Instance details

Defined in Michelson.Optimizer

Methods

def :: OptimizerConf #

Default MorleyLogs Source # 
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 #

ParameterScope arg => Default (SomeEntryPointCallT arg) Source # 
Instance details

Defined in Michelson.Typed.EntryPoints

Methods

def :: SomeEntryPointCallT arg #

Default (DfsSettings x) Source # 
Instance details

Defined in Michelson.Typed.Util

Methods

def :: DfsSettings x #

Default a => Default (Parser a) Source # 
Instance details

Defined in Michelson.Parser.Types

Methods

def :: Parser a #

Default (UStore a) Source # 
Instance details

Defined in Lorentz.UStore.Types

Methods

def :: UStore a #

Default (Store a) Source # 
Instance details

Defined in Lorentz.Store

Methods

def :: Store a #

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 (Annotation tag) Source # 
Instance details

Defined in Michelson.Untyped.Annotation

Methods

def :: Annotation tag #

param ~ arg => Default (EntryPointCallT param arg) Source #

Calls the default entrypoint.

Instance details

Defined in Michelson.Typed.EntryPoints

Methods

def :: EntryPointCallT param arg #

Default (BigMap k v) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Methods

def :: BigMap k v #

Default (k |~> v) Source # 
Instance details

Defined in Lorentz.UStore.Types

Methods

def :: k |~> v #

Default other => Default (StorageSkeleton storeTemplate other) Source # 
Instance details

Defined in Lorentz.Store

Methods

def :: StorageSkeleton storeTemplate other #

(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) #