morley-0.3.0: Developer tools for the Michelson Language

Safe HaskellNone
LanguageHaskell2010

Lorentz.Value

Description

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

Synopsis

Documentation

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

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Address :: 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 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 (ContractAddr cp) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (ContractAddr cp) :: T Source #

IsoValue r => IsoValue (VoidResult r) Source # 
Instance details

Defined in Lorentz.Macro

Associated Types

type ToT (VoidResult r) :: T 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 (Lambda inp out) Source # 
Instance details

Defined in Lorentz.Base

Associated Types

type ToT (Lambda inp out) :: T Source #

Methods

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

fromVal :: Value (ToT (Lambda inp out)) -> Lambda inp out 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 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 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 KeyHash Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToCT KeyHash :: CT Source #

IsoCValue Address Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToCT Address :: 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

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 #

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 #

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

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

Defined in Data.Reflection

Methods

reflect :: proxy n -> Integer #

ArithOpHs Compare Integer Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Compare Integer Integer :: Type Source #

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 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 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 ArithResHs Compare Integer 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 #

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 #

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

ArithOpHs Compare Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Compare Natural 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 UnaryArithResHs Not Natural Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Neg Natural Source # 
Instance details

Defined in Lorentz.Arith

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 ArithResHs Compare Natural 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] #

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 #

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

ArithOpHs Compare MText MText Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Compare MText MText :: Type Source #

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

type ArithResHs Compare MText MText Source # 
Instance details

Defined in Lorentz.Arith

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 #

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 #

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

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 Compare Bool Bool Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Compare Bool 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_6989586621679763221Sym0 
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_6989586621679390831Sym0 
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_6989586621679763215Sym0 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings ShowsPrec_6989586621680280424Sym0 
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 ((||@#@$$) a6989586621679360125 :: TyFun Bool Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Bool

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

Defined in Data.Singletons.Prelude.Bool

SuppressUnusedWarnings (Compare_6989586621679390831Sym1 a6989586621679390829 :: TyFun Bool Ordering -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (ShowsPrec_6989586621680280424Sym1 a6989586621680280421 :: TyFun Bool (Symbol ~> Symbol) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Show

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

Defined in Data.Singletons.Prelude.Monad.Internal

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

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

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

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

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (IsJustSym0 :: TyFun (Maybe a6989586621679494604) 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 a6989586621680386719 ([a6989586621680386719] ~> Bool) -> Type) 
Instance details

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

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680450673Scrutinee_6989586621680450431Sym0 :: TyFun (t6989586621680450184 Bool) All -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680450664Scrutinee_6989586621680450433Sym0 :: TyFun (t6989586621680450184 Bool) Any -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Eq

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

Defined in Data.Singletons.Prelude.Eq

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

Defined in Data.Singletons.Prelude.Eq

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

Defined in Data.Singletons.Prelude.Bool

SuppressUnusedWarnings (TFHelper_6989586621679379643Sym0 :: TyFun a6989586621679379434 (a6989586621679379434 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (TFHelper_6989586621679379625Sym0 :: TyFun a6989586621679379434 (a6989586621679379434 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (TFHelper_6989586621679379607Sym0 :: TyFun a6989586621679379434 (a6989586621679379434 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (TFHelper_6989586621679379589Sym0 :: TyFun a6989586621679379434 (a6989586621679379434 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (Elem_6989586621680675558Sym0 :: TyFun a6989586621680450201 (Identity a6989586621680450201 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Identity

SuppressUnusedWarnings (Null_6989586621680675681Sym0 :: TyFun (Identity a6989586621680450199) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Identity

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (UntilSym0 :: TyFun (a6989586621679519836 ~> Bool) ((a6989586621679519836 ~> a6989586621679519836) ~> (a6989586621679519836 ~> a6989586621679519836)) -> 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 a6989586621680387783 :: TyFun [a6989586621680386731] Bool -> Type) 
Instance details

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

SuppressUnusedWarnings (ListelemSym1 a6989586621680387718 :: TyFun [a6989586621680386719] Bool -> Type) 
Instance details

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

SuppressUnusedWarnings (NotElemSym1 a6989586621679949092 :: TyFun [a6989586621679939208] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (IsSuffixOfSym1 a6989586621679949717 :: TyFun [a6989586621679939211] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (IsPrefixOfSym1 a6989586621679949126 :: TyFun [a6989586621679939212] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (IsInfixOfSym1 a6989586621679949364 :: TyFun [a6989586621679939210] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (ElemSym1 a6989586621679949099 :: TyFun [a6989586621679939209] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (AnySym1 a6989586621679949357 :: TyFun [a6989586621679939229] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (AllSym1 a6989586621679949412 :: TyFun [a6989586621679939230] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (IsRightSym0 :: TyFun (Either a6989586621680431630 b6989586621680431631) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Either

SuppressUnusedWarnings (IsLeftSym0 :: TyFun (Either a6989586621680431632 b6989586621680431633) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Either

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

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Elem_bySym1 a6989586621679948384 :: TyFun a6989586621679939126 ([a6989586621679939126] ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (NotElemSym0 :: TyFun a6989586621680450095 (t6989586621680450094 a6989586621680450095 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680451904Sym0 :: TyFun a6989586621680450201 (t6989586621680450184 a6989586621680450201 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680451737Sym0 :: TyFun a6989586621680450201 (t6989586621680450184 a6989586621680450201 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680451570Sym0 :: TyFun a6989586621680450201 (t6989586621680450184 a6989586621680450201 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680451233Sym0 :: TyFun a6989586621680450201 (t6989586621680450184 a6989586621680450201 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680451110Sym0 :: TyFun a6989586621680450201 (t6989586621680450184 a6989586621680450201 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (ElemSym0 :: TyFun a6989586621680450201 (t6989586621680450184 a6989586621680450201 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (DefaultEqSym1 a6989586621679363148 :: TyFun k6989586621679363147 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Eq

SuppressUnusedWarnings ((==@#@$$) x6989586621679363154 :: TyFun a6989586621679363153 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Eq

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

Defined in Data.Singletons.Prelude.Eq

SuppressUnusedWarnings (Bool_Sym1 a6989586621679359139 :: TyFun a6989586621679359133 (Bool ~> a6989586621679359133) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Bool

SuppressUnusedWarnings (TFHelper_6989586621679379643Sym1 a6989586621679379641 :: TyFun a6989586621679379434 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (TFHelper_6989586621679379625Sym1 a6989586621679379623 :: TyFun a6989586621679379434 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (TFHelper_6989586621679379607Sym1 a6989586621679379605 :: TyFun a6989586621679379434 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (TFHelper_6989586621679379589Sym1 a6989586621679379587 :: TyFun a6989586621679379434 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings ((>@#@$$) arg6989586621679379535 :: TyFun a6989586621679379434 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings ((>=@#@$$) arg6989586621679379539 :: TyFun a6989586621679379434 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings ((<@#@$$) arg6989586621679379527 :: TyFun a6989586621679379434 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (TFHelper_6989586621680882310Sym0 :: TyFun (Arg a6989586621680881093 b6989586621680881094) (Arg a6989586621680881093 b6989586621680881094 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

SuppressUnusedWarnings (Elem_6989586621680675558Sym1 a6989586621680675556 :: TyFun (Identity a6989586621680450201) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Identity

SuppressUnusedWarnings (Let6989586621679948642ZsSym0 :: TyFun (k1 ~> (a6989586621679939149 ~> Bool)) (TyFun k1 (TyFun [a6989586621679939149] [a6989586621679939149] -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621679948642YsSym0 :: TyFun (k1 ~> (a6989586621679939149 ~> Bool)) (TyFun k1 (TyFun [a6989586621679939149] [a6989586621679939149] -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621679948400NubBy'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_6989586621679949733Sym0 :: TyFun (a6989586621679939246 ~> Bool) (TyFun k (TyFun a6989586621679939246 (TyFun [a6989586621679939246] [a6989586621679939246] -> Type) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680450654Scrutinee_6989586621680450435Sym0 :: TyFun (a6989586621680450187 ~> Bool) (TyFun (t6989586621680450184 a6989586621680450187) Any -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680450641Scrutinee_6989586621680450437Sym0 :: TyFun (a6989586621680450187 ~> Bool) (TyFun (t6989586621680450184 a6989586621680450187) All -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680450556Scrutinee_6989586621680450443Sym0 :: TyFun (a6989586621680450187 ~> Bool) (TyFun (t6989586621680450184 a6989586621680450187) (First a6989586621680450187) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Lambda_6989586621680450557Sym0 :: TyFun (a6989586621679072630 ~> Bool) (TyFun k (TyFun a6989586621679072630 (First a6989586621679072630) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (FindSym0 :: TyFun (a6989586621680450093 ~> Bool) (t6989586621680450092 a6989586621680450093 ~> Maybe a6989586621680450093) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (AnySym0 :: TyFun (a6989586621680450103 ~> Bool) (t6989586621680450102 a6989586621680450103 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (AllSym0 :: TyFun (a6989586621680450101 ~> Bool) (t6989586621680450100 a6989586621680450101 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621679519972GoSym0 :: 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 a6989586621679359140 a6989586621679359139 :: TyFun Bool a6989586621679359133 -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Bool

SuppressUnusedWarnings (Elem_bySym2 a6989586621679948385 a6989586621679948384 :: TyFun [a6989586621679939126] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621679948439Scrutinee_6989586621679939827Sym1 n6989586621679948437 :: TyFun k Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Null_6989586621680452027Sym0 :: TyFun (t6989586621680450184 a6989586621680450199) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Null_6989586621680451860Sym0 :: TyFun (t6989586621680450184 a6989586621680450199) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Null_6989586621680451693Sym0 :: TyFun (t6989586621680450184 a6989586621680450199) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Null_6989586621680451547Sym0 :: TyFun (t6989586621680450184 a6989586621680450199) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Null_6989586621680451371Sym0 :: TyFun (t6989586621680450184 a6989586621680450199) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Null_6989586621680451073Sym0 :: TyFun (t6989586621680450184 a6989586621680450199) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (NullSym0 :: TyFun (t6989586621680450184 a6989586621680450199) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (NotElemSym1 a6989586621680450577 t6989586621680450094 :: TyFun (t6989586621680450094 a6989586621680450095) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680451904Sym1 a6989586621680451902 t6989586621680450184 :: TyFun (t6989586621680450184 a6989586621680450201) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680451737Sym1 a6989586621680451735 t6989586621680450184 :: TyFun (t6989586621680450184 a6989586621680450201) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680451570Sym1 a6989586621680451568 t6989586621680450184 :: TyFun (t6989586621680450184 a6989586621680450201) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680451233Sym1 a6989586621680451231 t6989586621680450184 :: TyFun (t6989586621680450184 a6989586621680450201) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680451110Sym1 a6989586621680451108 t6989586621680450184 :: TyFun (t6989586621680450184 a6989586621680450201) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (ElemSym1 arg6989586621680450851 t6989586621680450184 :: TyFun (t6989586621680450184 a6989586621680450201) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (AnySym1 a6989586621680450648 t6989586621680450102 :: TyFun (t6989586621680450102 a6989586621680450103) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (AllSym1 a6989586621680450635 t6989586621680450100 :: TyFun (t6989586621680450100 a6989586621680450101) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (TFHelper_6989586621680882310Sym1 a6989586621680882308 :: TyFun (Arg a6989586621680881093 b6989586621680881094) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621679948410Scrutinee_6989586621679939833Sym0 :: 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 (Let6989586621679949737Scrutinee_6989586621679939805Sym1 p6989586621679949731 :: TyFun k1 (TyFun [a6989586621679939246] (TyFun k Bool -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621679949118Scrutinee_6989586621679939831Sym1 l6989586621679949108 :: TyFun k2 (TyFun k1 (TyFun [k2] Bool -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621679948536Scrutinee_6989586621679939811Sym1 n6989586621679948533 :: TyFun k1 (TyFun k2 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621679948522Scrutinee_6989586621679939813Sym1 n6989586621679948519 :: TyFun k1 (TyFun k2 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621679948426Scrutinee_6989586621679939829Sym1 x6989586621679948423 :: TyFun k1 (TyFun k2 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Lambda_6989586621680451060Sym1 a_69895866216804510556989586621680451059 :: TyFun k1 (TyFun k2 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621679739600Scrutinee_6989586621679739366Sym0 :: 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 (Let6989586621679949737Scrutinee_6989586621679939805Sym2 x6989586621679949735 p6989586621679949731 :: TyFun [a6989586621679939246] (TyFun k Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621679949118Scrutinee_6989586621679939831Sym2 x6989586621679949115 l6989586621679949108 :: TyFun k1 (TyFun [k2] Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621679948536Scrutinee_6989586621679939811Sym2 x6989586621679948534 n6989586621679948533 :: TyFun k1 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621679948522Scrutinee_6989586621679939813Sym2 x6989586621679948520 n6989586621679948519 :: TyFun k1 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621679948507Scrutinee_6989586621679939823Sym2 x6989586621679948504 key6989586621679948503 :: TyFun k1 (TyFun k2 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621679948426Scrutinee_6989586621679939829Sym2 xs6989586621679948424 x6989586621679948423 :: TyFun k1 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621679948410Scrutinee_6989586621679939833Sym2 l6989586621679948399 eq6989586621679948398 :: TyFun k3 (TyFun k1 (TyFun [k3] Bool -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Lambda_6989586621680451060Sym2 t6989586621680451067 a_69895866216804510556989586621680451059 :: TyFun k1 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621679739523Scrutinee_6989586621679739380Sym0 :: 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 (Let6989586621679739466Scrutinee_6989586621679739390Sym0 :: 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_6989586621679949392Sym0 :: TyFun (b6989586621679544160 ~> (a6989586621679939229 ~> Bool)) (TyFun k1 (TyFun k2 (TyFun a6989586621679939229 (TyFun [a6989586621679939229] (TyFun b6989586621679544160 (m6989586621679544156 b6989586621679544160) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621679949118Scrutinee_6989586621679939831Sym3 xs6989586621679949116 x6989586621679949115 l6989586621679949108 :: TyFun [k2] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621679949737Scrutinee_6989586621679939805Sym3 xs6989586621679949736 x6989586621679949735 p6989586621679949731 :: TyFun k Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621679948507Scrutinee_6989586621679939823Sym3 y6989586621679948505 x6989586621679948504 key6989586621679948503 :: TyFun k1 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621679948410Scrutinee_6989586621679939833Sym3 y6989586621679948407 l6989586621679948399 eq6989586621679948398 :: TyFun k1 (TyFun [k3] Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621679739600Scrutinee_6989586621679739366Sym2 y6989586621679739591 x06989586621679739590 :: TyFun k3 (TyFun k1 (TyFun k2 Bool -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621679739523Scrutinee_6989586621679739380Sym1 x16989586621679739518 :: 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 (Let6989586621679739466Scrutinee_6989586621679739390Sym1 x16989586621679739461 :: 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 (Let6989586621679948410Scrutinee_6989586621679939833Sym4 ys6989586621679948408 y6989586621679948407 l6989586621679948399 eq6989586621679948398 :: TyFun [k3] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621679739600Scrutinee_6989586621679739366Sym3 x6989586621679739599 y6989586621679739591 x06989586621679739590 :: TyFun k1 (TyFun k2 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621679739523Scrutinee_6989586621679739380Sym2 x26989586621679739519 x16989586621679739518 :: TyFun k5 (TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621679739466Scrutinee_6989586621679739390Sym2 x26989586621679739462 x16989586621679739461 :: TyFun k5 (TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621679739600Scrutinee_6989586621679739366Sym4 arg_69895866216797393626989586621679739586 x6989586621679739599 y6989586621679739591 x06989586621679739590 :: TyFun k1 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621679739523Scrutinee_6989586621679739380Sym3 y6989586621679739520 x26989586621679739519 x16989586621679739518 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621679739466Scrutinee_6989586621679739390Sym3 y6989586621679739463 x26989586621679739462 x16989586621679739461 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621679739523Scrutinee_6989586621679739380Sym4 arg_69895866216797393746989586621679739513 y6989586621679739520 x26989586621679739519 x16989586621679739518 :: TyFun k1 (TyFun k2 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621679739466Scrutinee_6989586621679739390Sym4 arg_69895866216797393846989586621679739456 y6989586621679739463 x26989586621679739462 x16989586621679739461 :: TyFun k1 (TyFun k2 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621679739523Scrutinee_6989586621679739380Sym5 arg_69895866216797393766989586621679739514 arg_69895866216797393746989586621679739513 y6989586621679739520 x26989586621679739519 x16989586621679739518 :: TyFun k1 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621679739466Scrutinee_6989586621679739390Sym5 arg_69895866216797393866989586621679739457 arg_69895866216797393846989586621679739456 y6989586621679739463 x26989586621679739462 x16989586621679739461 :: 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_6989586621679735353Sym0
type MinBound 
Instance details

Defined in Data.Singletons.Prelude.Enum

type MinBound = MinBound_6989586621679735351Sym0
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__6989586621680262174Sym0 :: TyFun Bool Symbol -> Type) arg
type FromEnum (a :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Enum

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

Defined in Data.Singletons.Prelude.Enum

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

Defined in Data.Singletons.Prelude.Enum

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

Defined in Data.Singletons.Prelude.Enum

type Succ (arg :: Bool) = Apply (Succ_6989586621679739643Sym0 :: 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_6989586621680262185Sym0 :: 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_6989586621679739663Sym0 :: 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_6989586621679379679Sym0 :: 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_6989586621679379661Sym0 :: 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_6989586621679379643Sym0 :: 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_6989586621679379625Sym0 :: 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_6989586621679379607Sym0 :: 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_6989586621679379589Sym0 :: 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_6989586621679390831Sym0 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_6989586621679364579 a b
type ArithResHs Compare Bool Bool Source # 
Instance details

Defined in Lorentz.Arith

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_6989586621680280424Sym0 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_6989586621679739679Sym0 :: TyFun Bool (Bool ~> (Bool ~> [Bool])) -> Type) arg1) arg2) arg3
type Apply NotSym0 (a6989586621679360425 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Bool

type Apply NotSym0 (a6989586621679360425 :: Bool) = Not a6989586621679360425
type Apply ToEnum_6989586621679763215Sym0 (a6989586621679763214 :: Nat) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply ToEnum_6989586621679763215Sym0 (a6989586621679763214 :: Nat) = ToEnum_6989586621679763215 a6989586621679763214
type Apply GetAllSym0 (a6989586621679819658 :: All) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply GetAllSym0 (a6989586621679819658 :: All) = GetAll a6989586621679819658
type Apply GetAnySym0 (a6989586621679819672 :: Any) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply GetAnySym0 (a6989586621679819672 :: Any) = GetAny a6989586621679819672
type Apply FromEnum_6989586621679763221Sym0 (a6989586621679763220 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply FromEnum_6989586621679763221Sym0 (a6989586621679763220 :: Bool) = FromEnum_6989586621679763221 a6989586621679763220
type Apply All_Sym0 (a6989586621679852512 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply All_Sym0 (a6989586621679852512 :: Bool) = All_ a6989586621679852512
type Apply AllSym0 (t6989586621679819661 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply AllSym0 (t6989586621679819661 :: Bool) = All t6989586621679819661
type Apply Any_Sym0 (a6989586621679852511 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply Any_Sym0 (a6989586621679852511 :: Bool) = Any_ a6989586621679852511
type Apply AnySym0 (t6989586621679819675 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply AnySym0 (t6989586621679819675 :: Bool) = Any t6989586621679819675
type Apply ((||@#@$$) a6989586621679360125 :: TyFun Bool Bool -> Type) (b6989586621679360126 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Bool

type Apply ((||@#@$$) a6989586621679360125 :: TyFun Bool Bool -> Type) (b6989586621679360126 :: Bool) = a6989586621679360125 || b6989586621679360126
type Apply ((&&@#@$$) a6989586621679359884 :: TyFun Bool Bool -> Type) (b6989586621679359885 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Bool

type Apply ((&&@#@$$) a6989586621679359884 :: TyFun Bool Bool -> Type) (b6989586621679359885 :: Bool) = a6989586621679359884 && b6989586621679359885
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_6989586621679390831Sym1 a6989586621679390829 :: TyFun Bool Ordering -> Type) (a6989586621679390830 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Compare_6989586621679390831Sym1 a6989586621679390829 :: TyFun Bool Ordering -> Type) (a6989586621679390830 :: Bool) = Compare_6989586621679390831 a6989586621679390829 a6989586621679390830
type Apply (Let6989586621680441980Scrutinee_6989586621680441943Sym1 x6989586621680441973 :: TyFun k1 Bool -> Type) (y6989586621680441974 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680441980Scrutinee_6989586621680441943Sym1 x6989586621680441973 :: TyFun k1 Bool -> Type) (y6989586621680441974 :: k1) = Let6989586621680441980Scrutinee_6989586621680441943 x6989586621680441973 y6989586621680441974
type Apply (Let6989586621680442007Scrutinee_6989586621680441945Sym1 x6989586621680442000 :: TyFun k1 Bool -> Type) (y6989586621680442001 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680442007Scrutinee_6989586621680441945Sym1 x6989586621680442000 :: TyFun k1 Bool -> Type) (y6989586621680442001 :: k1) = Let6989586621680442007Scrutinee_6989586621680441945 x6989586621680442000 y6989586621680442001
type Apply ((==@#@$$) x6989586621679363154 :: TyFun a Bool -> Type) (y6989586621679363155 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Eq

type Apply ((==@#@$$) x6989586621679363154 :: TyFun a Bool -> Type) (y6989586621679363155 :: a) = x6989586621679363154 == y6989586621679363155
type Apply ((/=@#@$$) x6989586621679363156 :: TyFun a Bool -> Type) (y6989586621679363157 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Eq

type Apply ((/=@#@$$) x6989586621679363156 :: TyFun a Bool -> Type) (y6989586621679363157 :: a) = x6989586621679363156 /= y6989586621679363157
type Apply (DefaultEqSym1 a6989586621679363148 :: TyFun k Bool -> Type) (b6989586621679363149 :: k) 
Instance details

Defined in Data.Singletons.Prelude.Eq

type Apply (DefaultEqSym1 a6989586621679363148 :: TyFun k Bool -> Type) (b6989586621679363149 :: k) = DefaultEq a6989586621679363148 b6989586621679363149
type Apply (Let6989586621679379557Scrutinee_6989586621679379452Sym1 x6989586621679379555 :: TyFun k1 Bool -> Type) (y6989586621679379556 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Let6989586621679379557Scrutinee_6989586621679379452Sym1 x6989586621679379555 :: TyFun k1 Bool -> Type) (y6989586621679379556 :: k1) = Let6989586621679379557Scrutinee_6989586621679379452 x6989586621679379555 y6989586621679379556
type Apply (TFHelper_6989586621679379643Sym1 a6989586621679379641 :: TyFun a Bool -> Type) (a6989586621679379642 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (TFHelper_6989586621679379643Sym1 a6989586621679379641 :: TyFun a Bool -> Type) (a6989586621679379642 :: a) = TFHelper_6989586621679379643 a6989586621679379641 a6989586621679379642
type Apply (TFHelper_6989586621679379625Sym1 a6989586621679379623 :: TyFun a Bool -> Type) (a6989586621679379624 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (TFHelper_6989586621679379625Sym1 a6989586621679379623 :: TyFun a Bool -> Type) (a6989586621679379624 :: a) = TFHelper_6989586621679379625 a6989586621679379623 a6989586621679379624
type Apply (TFHelper_6989586621679379607Sym1 a6989586621679379605 :: TyFun a Bool -> Type) (a6989586621679379606 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (TFHelper_6989586621679379607Sym1 a6989586621679379605 :: TyFun a Bool -> Type) (a6989586621679379606 :: a) = TFHelper_6989586621679379607 a6989586621679379605 a6989586621679379606
type Apply (TFHelper_6989586621679379589Sym1 a6989586621679379587 :: TyFun a Bool -> Type) (a6989586621679379588 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (TFHelper_6989586621679379589Sym1 a6989586621679379587 :: TyFun a Bool -> Type) (a6989586621679379588 :: a) = TFHelper_6989586621679379589 a6989586621679379587 a6989586621679379588
type Apply ((<=@#@$$) arg6989586621679379531 :: TyFun a Bool -> Type) (arg6989586621679379532 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply ((<=@#@$$) arg6989586621679379531 :: TyFun a Bool -> Type) (arg6989586621679379532 :: a) = arg6989586621679379531 <= arg6989586621679379532
type Apply ((>=@#@$$) arg6989586621679379539 :: TyFun a Bool -> Type) (arg6989586621679379540 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply ((>=@#@$$) arg6989586621679379539 :: TyFun a Bool -> Type) (arg6989586621679379540 :: a) = arg6989586621679379539 >= arg6989586621679379540
type Apply ((>@#@$$) arg6989586621679379535 :: TyFun a Bool -> Type) (arg6989586621679379536 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply ((>@#@$$) arg6989586621679379535 :: TyFun a Bool -> Type) (arg6989586621679379536 :: a) = arg6989586621679379535 > arg6989586621679379536
type Apply (Let6989586621679379671Scrutinee_6989586621679379466Sym1 x6989586621679379669 :: TyFun k1 Bool -> Type) (y6989586621679379670 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Let6989586621679379671Scrutinee_6989586621679379466Sym1 x6989586621679379669 :: TyFun k1 Bool -> Type) (y6989586621679379670 :: k1) = Let6989586621679379671Scrutinee_6989586621679379466 x6989586621679379669 y6989586621679379670
type Apply (Let6989586621679379653Scrutinee_6989586621679379464Sym1 x6989586621679379651 :: TyFun k1 Bool -> Type) (y6989586621679379652 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Let6989586621679379653Scrutinee_6989586621679379464Sym1 x6989586621679379651 :: TyFun k1 Bool -> Type) (y6989586621679379652 :: k1) = Let6989586621679379653Scrutinee_6989586621679379464 x6989586621679379651 y6989586621679379652
type Apply (Let6989586621679379562Scrutinee_6989586621679379454Sym1 x6989586621679379555 :: TyFun k1 Bool -> Type) (y6989586621679379556 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Let6989586621679379562Scrutinee_6989586621679379454Sym1 x6989586621679379555 :: TyFun k1 Bool -> Type) (y6989586621679379556 :: k1) = Let6989586621679379562Scrutinee_6989586621679379454 x6989586621679379555 y6989586621679379556
type Apply ((<@#@$$) arg6989586621679379527 :: TyFun a Bool -> Type) (arg6989586621679379528 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply ((<@#@$$) arg6989586621679379527 :: TyFun a Bool -> Type) (arg6989586621679379528 :: a) = arg6989586621679379527 < arg6989586621679379528
type Apply (Let6989586621679948439Scrutinee_6989586621679939827Sym1 n6989586621679948437 :: TyFun k Bool -> Type) (x6989586621679948438 :: k) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948439Scrutinee_6989586621679939827Sym1 n6989586621679948437 :: TyFun k Bool -> Type) (x6989586621679948438 :: k) = Let6989586621679948439Scrutinee_6989586621679939827 n6989586621679948437 x6989586621679948438
type Apply (Bool_Sym2 a6989586621679359140 a6989586621679359139 :: TyFun Bool a -> Type) (a6989586621679359141 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Bool

type Apply (Bool_Sym2 a6989586621679359140 a6989586621679359139 :: TyFun Bool a -> Type) (a6989586621679359141 :: Bool) = Bool_ a6989586621679359140 a6989586621679359139 a6989586621679359141
type Apply (Let6989586621679948426Scrutinee_6989586621679939829Sym2 xs6989586621679948424 x6989586621679948423 :: TyFun k3 Bool -> Type) (n6989586621679948425 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948426Scrutinee_6989586621679939829Sym2 xs6989586621679948424 x6989586621679948423 :: TyFun k3 Bool -> Type) (n6989586621679948425 :: k3) = Let6989586621679948426Scrutinee_6989586621679939829 xs6989586621679948424 x6989586621679948423 n6989586621679948425
type Apply (Let6989586621679948522Scrutinee_6989586621679939813Sym2 x6989586621679948520 n6989586621679948519 :: TyFun k3 Bool -> Type) (xs6989586621679948521 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948522Scrutinee_6989586621679939813Sym2 x6989586621679948520 n6989586621679948519 :: TyFun k3 Bool -> Type) (xs6989586621679948521 :: k3) = Let6989586621679948522Scrutinee_6989586621679939813 x6989586621679948520 n6989586621679948519 xs6989586621679948521
type Apply (Let6989586621679948536Scrutinee_6989586621679939811Sym2 x6989586621679948534 n6989586621679948533 :: TyFun k3 Bool -> Type) (xs6989586621679948535 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948536Scrutinee_6989586621679939811Sym2 x6989586621679948534 n6989586621679948533 :: TyFun k3 Bool -> Type) (xs6989586621679948535 :: k3) = Let6989586621679948536Scrutinee_6989586621679939811 x6989586621679948534 n6989586621679948533 xs6989586621679948535
type Apply (Lambda_6989586621680451060Sym2 t6989586621680451067 a_69895866216804510556989586621680451059 :: TyFun k3 Bool -> Type) (t6989586621680451068 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Lambda_6989586621680451060Sym2 t6989586621680451067 a_69895866216804510556989586621680451059 :: TyFun k3 Bool -> Type) (t6989586621680451068 :: k3) = Lambda_6989586621680451060 t6989586621680451067 a_69895866216804510556989586621680451059 t6989586621680451068
type Apply (Let6989586621679948507Scrutinee_6989586621679939823Sym3 y6989586621679948505 x6989586621679948504 key6989586621679948503 :: TyFun k3 Bool -> Type) (xys6989586621679948506 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948507Scrutinee_6989586621679939823Sym3 y6989586621679948505 x6989586621679948504 key6989586621679948503 :: TyFun k3 Bool -> Type) (xys6989586621679948506 :: k3) = Let6989586621679948507Scrutinee_6989586621679939823 y6989586621679948505 x6989586621679948504 key6989586621679948503 xys6989586621679948506
type Apply (Let6989586621679949737Scrutinee_6989586621679939805Sym3 xs6989586621679949736 x6989586621679949735 p6989586621679949731 :: TyFun k Bool -> Type) (a_69895866216799497296989586621679949732 :: k) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679949737Scrutinee_6989586621679939805Sym3 xs6989586621679949736 x6989586621679949735 p6989586621679949731 :: TyFun k Bool -> Type) (a_69895866216799497296989586621679949732 :: k) = Let6989586621679949737Scrutinee_6989586621679939805 xs6989586621679949736 x6989586621679949735 p6989586621679949731 a_69895866216799497296989586621679949732
type Apply (Let6989586621679739600Scrutinee_6989586621679739366Sym4 arg_69895866216797393626989586621679739586 x6989586621679739599 y6989586621679739591 x06989586621679739590 :: TyFun k4 Bool -> Type) (arg_69895866216797393646989586621679739587 :: k4) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621679739600Scrutinee_6989586621679739366Sym4 arg_69895866216797393626989586621679739586 x6989586621679739599 y6989586621679739591 x06989586621679739590 :: TyFun k4 Bool -> Type) (arg_69895866216797393646989586621679739587 :: k4) = Let6989586621679739600Scrutinee_6989586621679739366 arg_69895866216797393626989586621679739586 x6989586621679739599 y6989586621679739591 x06989586621679739590 arg_69895866216797393646989586621679739587
type Apply (Let6989586621679739466Scrutinee_6989586621679739390Sym5 arg_69895866216797393866989586621679739457 arg_69895866216797393846989586621679739456 y6989586621679739463 x26989586621679739462 x16989586621679739461 :: TyFun k5 Bool -> Type) (arg_69895866216797393886989586621679739458 :: k5) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621679739466Scrutinee_6989586621679739390Sym5 arg_69895866216797393866989586621679739457 arg_69895866216797393846989586621679739456 y6989586621679739463 x26989586621679739462 x16989586621679739461 :: TyFun k5 Bool -> Type) (arg_69895866216797393886989586621679739458 :: k5) = Let6989586621679739466Scrutinee_6989586621679739390 arg_69895866216797393866989586621679739457 arg_69895866216797393846989586621679739456 y6989586621679739463 x26989586621679739462 x16989586621679739461 arg_69895866216797393886989586621679739458
type Apply (Let6989586621679739523Scrutinee_6989586621679739380Sym5 arg_69895866216797393766989586621679739514 arg_69895866216797393746989586621679739513 y6989586621679739520 x26989586621679739519 x16989586621679739518 :: TyFun k5 Bool -> Type) (arg_69895866216797393786989586621679739515 :: k5) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621679739523Scrutinee_6989586621679739380Sym5 arg_69895866216797393766989586621679739514 arg_69895866216797393746989586621679739513 y6989586621679739520 x26989586621679739519 x16989586621679739518 :: TyFun k5 Bool -> Type) (arg_69895866216797393786989586621679739515 :: k5) = Let6989586621679739523Scrutinee_6989586621679739380 arg_69895866216797393766989586621679739514 arg_69895866216797393746989586621679739513 y6989586621679739520 x26989586621679739519 x16989586621679739518 arg_69895866216797393786989586621679739515
type Apply OrSym0 (a6989586621679949419 :: [Bool]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply OrSym0 (a6989586621679949419 :: [Bool]) = Or a6989586621679949419
type Apply AndSym0 (a6989586621679949423 :: [Bool]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

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

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

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.Maybe

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

Defined in Data.Singletons.Prelude.Maybe

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

type Apply (OrSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680450661 :: t Bool) = Or a6989586621680450661
type Apply (Null_6989586621680675681Sym0 :: TyFun (Identity a) Bool -> Type) (a6989586621680675680 :: Identity a) 
Instance details

Defined in Data.Singletons.Prelude.Identity

type Apply (Null_6989586621680675681Sym0 :: TyFun (Identity a) Bool -> Type) (a6989586621680675680 :: Identity a) = Null_6989586621680675681 a6989586621680675680
type Apply (Let6989586621680450673Scrutinee_6989586621680450431Sym0 :: TyFun (t6989586621680450184 Bool) All -> Type) (x6989586621680450672 :: t6989586621680450184 Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680450673Scrutinee_6989586621680450431Sym0 :: TyFun (t6989586621680450184 Bool) All -> Type) (x6989586621680450672 :: t6989586621680450184 Bool) = Let6989586621680450673Scrutinee_6989586621680450431 x6989586621680450672
type Apply (Let6989586621680450664Scrutinee_6989586621680450433Sym0 :: TyFun (t6989586621680450184 Bool) Any -> Type) (x6989586621680450663 :: t6989586621680450184 Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680450664Scrutinee_6989586621680450433Sym0 :: TyFun (t6989586621680450184 Bool) Any -> Type) (x6989586621680450663 :: t6989586621680450184 Bool) = Let6989586621680450664Scrutinee_6989586621680450433 x6989586621680450663
type Apply (ListelemSym1 a6989586621680387718 :: TyFun [a] Bool -> Type) (a6989586621680387719 :: [a]) 
Instance details

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

type Apply (ListelemSym1 a6989586621680387718 :: TyFun [a] Bool -> Type) (a6989586621680387719 :: [a]) = Listelem a6989586621680387718 a6989586621680387719
type Apply (ListisPrefixOfSym1 a6989586621680387783 :: TyFun [a] Bool -> Type) (a6989586621680387784 :: [a]) 
Instance details

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

type Apply (ListisPrefixOfSym1 a6989586621680387783 :: TyFun [a] Bool -> Type) (a6989586621680387784 :: [a]) = ListisPrefixOf a6989586621680387783 a6989586621680387784
type Apply (NotElemSym1 a6989586621679949092 :: TyFun [a] Bool -> Type) (a6989586621679949093 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (NotElemSym1 a6989586621679949092 :: TyFun [a] Bool -> Type) (a6989586621679949093 :: [a]) = NotElem a6989586621679949092 a6989586621679949093
type Apply (ElemSym1 a6989586621679949099 :: TyFun [a] Bool -> Type) (a6989586621679949100 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ElemSym1 a6989586621679949099 :: TyFun [a] Bool -> Type) (a6989586621679949100 :: [a]) = Elem a6989586621679949099 a6989586621679949100
type Apply (IsPrefixOfSym1 a6989586621679949126 :: TyFun [a] Bool -> Type) (a6989586621679949127 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IsPrefixOfSym1 a6989586621679949126 :: TyFun [a] Bool -> Type) (a6989586621679949127 :: [a]) = IsPrefixOf a6989586621679949126 a6989586621679949127
type Apply (AnySym1 a6989586621679949357 :: TyFun [a] Bool -> Type) (a6989586621679949358 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (AnySym1 a6989586621679949357 :: TyFun [a] Bool -> Type) (a6989586621679949358 :: [a]) = Any a6989586621679949357 a6989586621679949358
type Apply (IsInfixOfSym1 a6989586621679949364 :: TyFun [a] Bool -> Type) (a6989586621679949365 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IsInfixOfSym1 a6989586621679949364 :: TyFun [a] Bool -> Type) (a6989586621679949365 :: [a]) = IsInfixOf a6989586621679949364 a6989586621679949365
type Apply (AllSym1 a6989586621679949412 :: TyFun [a] Bool -> Type) (a6989586621679949413 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (AllSym1 a6989586621679949412 :: TyFun [a] Bool -> Type) (a6989586621679949413 :: [a]) = All a6989586621679949412 a6989586621679949413
type Apply (IsSuffixOfSym1 a6989586621679949717 :: TyFun [a] Bool -> Type) (a6989586621679949718 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IsSuffixOfSym1 a6989586621679949717 :: TyFun [a] Bool -> Type) (a6989586621679949718 :: [a]) = IsSuffixOf a6989586621679949717 a6989586621679949718
type Apply (Elem_6989586621680675558Sym1 a6989586621680675556 :: TyFun (Identity a) Bool -> Type) (a6989586621680675557 :: Identity a) 
Instance details

Defined in Data.Singletons.Prelude.Identity

type Apply (Elem_6989586621680675558Sym1 a6989586621680675556 :: TyFun (Identity a) Bool -> Type) (a6989586621680675557 :: Identity a) = Elem_6989586621680675558 a6989586621680675556 a6989586621680675557
type Apply (Elem_bySym2 a6989586621679948385 a6989586621679948384 :: TyFun [a] Bool -> Type) (a6989586621679948386 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Elem_bySym2 a6989586621679948385 a6989586621679948384 :: TyFun [a] Bool -> Type) (a6989586621679948386 :: [a]) = Elem_by a6989586621679948385 a6989586621679948384 a6989586621679948386
type Apply (Elem_6989586621680451110Sym1 a6989586621680451108 t :: TyFun (t a) Bool -> Type) (a6989586621680451109 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680451110Sym1 a6989586621680451108 t :: TyFun (t a) Bool -> Type) (a6989586621680451109 :: t a) = Elem_6989586621680451110 a6989586621680451108 a6989586621680451109
type Apply (Null_6989586621680451073Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680451072 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Null_6989586621680451073Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680451072 :: t a) = Null_6989586621680451073 a6989586621680451072
type Apply (AnySym1 a6989586621680450648 t :: TyFun (t a) Bool -> Type) (a6989586621680450649 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AnySym1 a6989586621680450648 t :: TyFun (t a) Bool -> Type) (a6989586621680450649 :: t a) = Any a6989586621680450648 a6989586621680450649
type Apply (ElemSym1 arg6989586621680450851 t :: TyFun (t a) Bool -> Type) (arg6989586621680450852 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ElemSym1 arg6989586621680450851 t :: TyFun (t a) Bool -> Type) (arg6989586621680450852 :: t a) = Elem arg6989586621680450851 arg6989586621680450852
type Apply (NotElemSym1 a6989586621680450577 t :: TyFun (t a) Bool -> Type) (a6989586621680450578 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (NotElemSym1 a6989586621680450577 t :: TyFun (t a) Bool -> Type) (a6989586621680450578 :: t a) = NotElem a6989586621680450577 a6989586621680450578
type Apply (NullSym0 :: TyFun (t a) Bool -> Type) (arg6989586621680450847 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (NullSym0 :: TyFun (t a) Bool -> Type) (arg6989586621680450847 :: t a) = Null arg6989586621680450847
type Apply (AllSym1 a6989586621680450635 t :: TyFun (t a) Bool -> Type) (a6989586621680450636 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AllSym1 a6989586621680450635 t :: TyFun (t a) Bool -> Type) (a6989586621680450636 :: t a) = All a6989586621680450635 a6989586621680450636
type Apply (Elem_6989586621680451233Sym1 a6989586621680451231 t :: TyFun (t a) Bool -> Type) (a6989586621680451232 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680451233Sym1 a6989586621680451231 t :: TyFun (t a) Bool -> Type) (a6989586621680451232 :: t a) = Elem_6989586621680451233 a6989586621680451231 a6989586621680451232
type Apply (Null_6989586621680451371Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680451370 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Null_6989586621680451371Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680451370 :: t a) = Null_6989586621680451371 a6989586621680451370
type Apply (Null_6989586621680451547Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680451546 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Null_6989586621680451547Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680451546 :: t a) = Null_6989586621680451547 a6989586621680451546
type Apply (Elem_6989586621680451570Sym1 a6989586621680451568 t :: TyFun (t a) Bool -> Type) (a6989586621680451569 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680451570Sym1 a6989586621680451568 t :: TyFun (t a) Bool -> Type) (a6989586621680451569 :: t a) = Elem_6989586621680451570 a6989586621680451568 a6989586621680451569
type Apply (Null_6989586621680451693Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680451692 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Null_6989586621680451693Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680451692 :: t a) = Null_6989586621680451693 a6989586621680451692
type Apply (Elem_6989586621680451737Sym1 a6989586621680451735 t :: TyFun (t a) Bool -> Type) (a6989586621680451736 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680451737Sym1 a6989586621680451735 t :: TyFun (t a) Bool -> Type) (a6989586621680451736 :: t a) = Elem_6989586621680451737 a6989586621680451735 a6989586621680451736
type Apply (Null_6989586621680451860Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680451859 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Null_6989586621680451860Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680451859 :: t a) = Null_6989586621680451860 a6989586621680451859
type Apply (Elem_6989586621680451904Sym1 a6989586621680451902 t :: TyFun (t a) Bool -> Type) (a6989586621680451903 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680451904Sym1 a6989586621680451902 t :: TyFun (t a) Bool -> Type) (a6989586621680451903 :: t a) = Elem_6989586621680451904 a6989586621680451902 a6989586621680451903
type Apply (Null_6989586621680452027Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680452026 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Null_6989586621680452027Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680452026 :: t a) = Null_6989586621680452027 a6989586621680452026
type Apply (Let6989586621679949118Scrutinee_6989586621679939831Sym3 xs6989586621679949116 x6989586621679949115 l6989586621679949108 :: TyFun [k1] Bool -> Type) (ls6989586621679949117 :: [k1]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679949118Scrutinee_6989586621679939831Sym3 xs6989586621679949116 x6989586621679949115 l6989586621679949108 :: TyFun [k1] Bool -> Type) (ls6989586621679949117 :: [k1]) = Let6989586621679949118Scrutinee_6989586621679939831 xs6989586621679949116 x6989586621679949115 l6989586621679949108 ls6989586621679949117
type Apply (Let6989586621679948410Scrutinee_6989586621679939833Sym4 ys6989586621679948408 y6989586621679948407 l6989586621679948399 eq6989586621679948398 :: TyFun [k2] Bool -> Type) (xs6989586621679948409 :: [k2]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948410Scrutinee_6989586621679939833Sym4 ys6989586621679948408 y6989586621679948407 l6989586621679948399 eq6989586621679948398 :: TyFun [k2] Bool -> Type) (xs6989586621679948409 :: [k2]) = Let6989586621679948410Scrutinee_6989586621679939833 ys6989586621679948408 y6989586621679948407 l6989586621679948399 eq6989586621679948398 xs6989586621679948409
type Apply (IsRightSym0 :: TyFun (Either a b) Bool -> Type) (a6989586621680431997 :: Either a b) 
Instance details

Defined in Data.Singletons.Prelude.Either

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

Defined in Data.Singletons.Prelude.Either

type Apply (IsLeftSym0 :: TyFun (Either a b) Bool -> Type) (a6989586621680431999 :: Either a b) = IsLeft a6989586621680431999
type Apply (TFHelper_6989586621680882310Sym1 a6989586621680882308 :: TyFun (Arg a b) Bool -> Type) (a6989586621680882309 :: Arg a b) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Apply (TFHelper_6989586621680882310Sym1 a6989586621680882308 :: TyFun (Arg a b) Bool -> Type) (a6989586621680882309 :: Arg a b) = TFHelper_6989586621680882310 a6989586621680882308 a6989586621680882309
type Apply (GuardSym0 :: TyFun Bool (f6989586621679544048 ()) -> Type) (a6989586621679544217 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

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

Defined in Test.Hspec.Core.Example

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

Defined in Data.Singletons.Prelude.Bool

type Apply (||@#@$) (a6989586621679360125 :: Bool) = (||@#@$$) a6989586621679360125
type Apply (&&@#@$) (a6989586621679359884 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Bool

type Apply (&&@#@$) (a6989586621679359884 :: Bool) = (&&@#@$$) a6989586621679359884
type Apply Compare_6989586621679390831Sym0 (a6989586621679390829 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply Compare_6989586621679390831Sym0 (a6989586621679390829 :: Bool) = Compare_6989586621679390831Sym1 a6989586621679390829
type Apply ShowsPrec_6989586621680280424Sym0 (a6989586621680280421 :: Nat) 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply ShowsPrec_6989586621680280424Sym0 (a6989586621680280421 :: Nat) = ShowsPrec_6989586621680280424Sym1 a6989586621680280421
type Apply (<=?@#@$) (a3530822107858468865 :: Nat) 
Instance details

Defined in Data.Singletons.TypeLits.Internal

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

Defined in Data.Singletons.Prelude.Show

type Apply ShowParenSym0 (a6989586621680262082 :: Bool) = ShowParenSym1 a6989586621680262082
type Apply (Let6989586621680441980Scrutinee_6989586621680441943Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621680441973 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680441980Scrutinee_6989586621680441943Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621680441973 :: k1) = Let6989586621680441980Scrutinee_6989586621680441943Sym1 x6989586621680441973
type Apply (Let6989586621680442007Scrutinee_6989586621680441945Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621680442000 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680442007Scrutinee_6989586621680441945Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621680442000 :: k1) = Let6989586621680442007Scrutinee_6989586621680441945Sym1 x6989586621680442000
type Apply (Let6989586621679379557Scrutinee_6989586621679379452Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679379555 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Let6989586621679379557Scrutinee_6989586621679379452Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679379555 :: k1) = Let6989586621679379557Scrutinee_6989586621679379452Sym1 x6989586621679379555
type Apply (Let6989586621679379671Scrutinee_6989586621679379466Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679379669 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Let6989586621679379671Scrutinee_6989586621679379466Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679379669 :: k1) = Let6989586621679379671Scrutinee_6989586621679379466Sym1 x6989586621679379669
type Apply (Let6989586621679379653Scrutinee_6989586621679379464Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679379651 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Let6989586621679379653Scrutinee_6989586621679379464Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679379651 :: k1) = Let6989586621679379653Scrutinee_6989586621679379464Sym1 x6989586621679379651
type Apply (Let6989586621679379562Scrutinee_6989586621679379454Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679379555 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Let6989586621679379562Scrutinee_6989586621679379454Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679379555 :: k1) = Let6989586621679379562Scrutinee_6989586621679379454Sym1 x6989586621679379555
type Apply (ListelemSym0 :: TyFun a6989586621680386719 ([a6989586621680386719] ~> Bool) -> Type) (a6989586621680387718 :: a6989586621680386719) 
Instance details

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

type Apply (ListelemSym0 :: TyFun a6989586621680386719 ([a6989586621680386719] ~> Bool) -> Type) (a6989586621680387718 :: a6989586621680386719) = ListelemSym1 a6989586621680387718
type Apply (NotElemSym0 :: TyFun a6989586621679939208 ([a6989586621679939208] ~> Bool) -> Type) (a6989586621679949092 :: a6989586621679939208) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (NotElemSym0 :: TyFun a6989586621679939208 ([a6989586621679939208] ~> Bool) -> Type) (a6989586621679949092 :: a6989586621679939208) = NotElemSym1 a6989586621679949092
type Apply (ElemSym0 :: TyFun a6989586621679939209 ([a6989586621679939209] ~> Bool) -> Type) (a6989586621679949099 :: a6989586621679939209) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ElemSym0 :: TyFun a6989586621679939209 ([a6989586621679939209] ~> Bool) -> Type) (a6989586621679949099 :: a6989586621679939209) = ElemSym1 a6989586621679949099
type Apply (ShowsPrec_6989586621680280424Sym1 a6989586621680280421 :: TyFun Bool (Symbol ~> Symbol) -> Type) (a6989586621680280422 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowsPrec_6989586621680280424Sym1 a6989586621680280421 :: TyFun Bool (Symbol ~> Symbol) -> Type) (a6989586621680280422 :: Bool) = ShowsPrec_6989586621680280424Sym2 a6989586621680280421 a6989586621680280422
type Apply (WhenSym0 :: TyFun Bool (f6989586621679544077 () ~> f6989586621679544077 ()) -> Type) (a6989586621679544465 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (WhenSym0 :: TyFun Bool (f6989586621679544077 () ~> f6989586621679544077 ()) -> Type) (a6989586621679544465 :: Bool) = (WhenSym1 a6989586621679544465 f6989586621679544077 :: TyFun (f6989586621679544077 ()) (f6989586621679544077 ()) -> Type)
type Apply ((==@#@$) :: TyFun a6989586621679363153 (a6989586621679363153 ~> Bool) -> Type) (x6989586621679363154 :: a6989586621679363153) 
Instance details

Defined in Data.Singletons.Prelude.Eq

type Apply ((==@#@$) :: TyFun a6989586621679363153 (a6989586621679363153 ~> Bool) -> Type) (x6989586621679363154 :: a6989586621679363153) = (==@#@$$) x6989586621679363154
type Apply ((/=@#@$) :: TyFun a6989586621679363153 (a6989586621679363153 ~> Bool) -> Type) (x6989586621679363156 :: a6989586621679363153) 
Instance details

Defined in Data.Singletons.Prelude.Eq

type Apply ((/=@#@$) :: TyFun a6989586621679363153 (a6989586621679363153 ~> Bool) -> Type) (x6989586621679363156 :: a6989586621679363153) = (/=@#@$$) x6989586621679363156
type Apply (DefaultEqSym0 :: TyFun k6989586621679363147 (k6989586621679363147 ~> Bool) -> Type) (a6989586621679363148 :: k6989586621679363147) 
Instance details

Defined in Data.Singletons.Prelude.Eq

type Apply (DefaultEqSym0 :: TyFun k6989586621679363147 (k6989586621679363147 ~> Bool) -> Type) (a6989586621679363148 :: k6989586621679363147) = DefaultEqSym1 a6989586621679363148
type Apply (Bool_Sym0 :: TyFun a6989586621679359133 (a6989586621679359133 ~> (Bool ~> a6989586621679359133)) -> Type) (a6989586621679359139 :: a6989586621679359133) 
Instance details

Defined in Data.Singletons.Prelude.Bool

type Apply (Bool_Sym0 :: TyFun a6989586621679359133 (a6989586621679359133 ~> (Bool ~> a6989586621679359133)) -> Type) (a6989586621679359139 :: a6989586621679359133) = Bool_Sym1 a6989586621679359139
type Apply (TFHelper_6989586621679379643Sym0 :: TyFun a6989586621679379434 (a6989586621679379434 ~> Bool) -> Type) (a6989586621679379641 :: a6989586621679379434) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (TFHelper_6989586621679379643Sym0 :: TyFun a6989586621679379434 (a6989586621679379434 ~> Bool) -> Type) (a6989586621679379641 :: a6989586621679379434) = TFHelper_6989586621679379643Sym1 a6989586621679379641
type Apply (TFHelper_6989586621679379625Sym0 :: TyFun a6989586621679379434 (a6989586621679379434 ~> Bool) -> Type) (a6989586621679379623 :: a6989586621679379434) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (TFHelper_6989586621679379625Sym0 :: TyFun a6989586621679379434 (a6989586621679379434 ~> Bool) -> Type) (a6989586621679379623 :: a6989586621679379434) = TFHelper_6989586621679379625Sym1 a6989586621679379623
type Apply (TFHelper_6989586621679379607Sym0 :: TyFun a6989586621679379434 (a6989586621679379434 ~> Bool) -> Type) (a6989586621679379605 :: a6989586621679379434) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (TFHelper_6989586621679379607Sym0 :: TyFun a6989586621679379434 (a6989586621679379434 ~> Bool) -> Type) (a6989586621679379605 :: a6989586621679379434) = TFHelper_6989586621679379607Sym1 a6989586621679379605
type Apply (TFHelper_6989586621679379589Sym0 :: TyFun a6989586621679379434 (a6989586621679379434 ~> Bool) -> Type) (a6989586621679379587 :: a6989586621679379434) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (TFHelper_6989586621679379589Sym0 :: TyFun a6989586621679379434 (a6989586621679379434 ~> Bool) -> Type) (a6989586621679379587 :: a6989586621679379434) = TFHelper_6989586621679379589Sym1 a6989586621679379587
type Apply ((<=@#@$) :: TyFun a6989586621679379434 (a6989586621679379434 ~> Bool) -> Type) (arg6989586621679379531 :: a6989586621679379434) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply ((<=@#@$) :: TyFun a6989586621679379434 (a6989586621679379434 ~> Bool) -> Type) (arg6989586621679379531 :: a6989586621679379434) = (<=@#@$$) arg6989586621679379531
type Apply ((>=@#@$) :: TyFun a6989586621679379434 (a6989586621679379434 ~> Bool) -> Type) (arg6989586621679379539 :: a6989586621679379434) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply ((>=@#@$) :: TyFun a6989586621679379434 (a6989586621679379434 ~> Bool) -> Type) (arg6989586621679379539 :: a6989586621679379434) = (>=@#@$$) arg6989586621679379539
type Apply ((>@#@$) :: TyFun a6989586621679379434 (a6989586621679379434 ~> Bool) -> Type) (arg6989586621679379535 :: a6989586621679379434) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply ((>@#@$) :: TyFun a6989586621679379434 (a6989586621679379434 ~> Bool) -> Type) (arg6989586621679379535 :: a6989586621679379434) = (>@#@$$) arg6989586621679379535
type Apply ((<@#@$) :: TyFun a6989586621679379434 (a6989586621679379434 ~> Bool) -> Type) (arg6989586621679379527 :: a6989586621679379434) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply ((<@#@$) :: TyFun a6989586621679379434 (a6989586621679379434 ~> Bool) -> Type) (arg6989586621679379527 :: a6989586621679379434) = (<@#@$$) arg6989586621679379527
type Apply (Elem_6989586621680675558Sym0 :: TyFun a6989586621680450201 (Identity a6989586621680450201 ~> Bool) -> Type) (a6989586621680675556 :: a6989586621680450201) 
Instance details

Defined in Data.Singletons.Prelude.Identity

type Apply (Elem_6989586621680675558Sym0 :: TyFun a6989586621680450201 (Identity a6989586621680450201 ~> Bool) -> Type) (a6989586621680675556 :: a6989586621680450201) = Elem_6989586621680675558Sym1 a6989586621680675556
type Apply (Let6989586621679948439Scrutinee_6989586621679939827Sym0 :: TyFun k1 (TyFun k Bool -> Type) -> Type) (n6989586621679948437 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948439Scrutinee_6989586621679939827Sym0 :: TyFun k1 (TyFun k Bool -> Type) -> Type) (n6989586621679948437 :: k1) = (Let6989586621679948439Scrutinee_6989586621679939827Sym1 n6989586621679948437 :: TyFun k Bool -> Type)
type Apply (Bool_Sym1 a6989586621679359139 :: TyFun a6989586621679359133 (Bool ~> a6989586621679359133) -> Type) (a6989586621679359140 :: a6989586621679359133) 
Instance details

Defined in Data.Singletons.Prelude.Bool

type Apply (Bool_Sym1 a6989586621679359139 :: TyFun a6989586621679359133 (Bool ~> a6989586621679359133) -> Type) (a6989586621679359140 :: a6989586621679359133) = Bool_Sym2 a6989586621679359139 a6989586621679359140
type Apply (Elem_bySym1 a6989586621679948384 :: TyFun a6989586621679939126 ([a6989586621679939126] ~> Bool) -> Type) (a6989586621679948385 :: a6989586621679939126) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Elem_bySym1 a6989586621679948384 :: TyFun a6989586621679939126 ([a6989586621679939126] ~> Bool) -> Type) (a6989586621679948385 :: a6989586621679939126) = Elem_bySym2 a6989586621679948384 a6989586621679948385
type Apply (Elem_6989586621680451110Sym0 :: TyFun a6989586621680450201 (t6989586621680450184 a6989586621680450201 ~> Bool) -> Type) (a6989586621680451108 :: a6989586621680450201) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680451110Sym0 :: TyFun a6989586621680450201 (t6989586621680450184 a6989586621680450201 ~> Bool) -> Type) (a6989586621680451108 :: a6989586621680450201) = (Elem_6989586621680451110Sym1 a6989586621680451108 t6989586621680450184 :: TyFun (t6989586621680450184 a6989586621680450201) Bool -> Type)
type Apply (ElemSym0 :: TyFun a6989586621680450201 (t6989586621680450184 a6989586621680450201 ~> Bool) -> Type) (arg6989586621680450851 :: a6989586621680450201) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ElemSym0 :: TyFun a6989586621680450201 (t6989586621680450184 a6989586621680450201 ~> Bool) -> Type) (arg6989586621680450851 :: a6989586621680450201) = (ElemSym1 arg6989586621680450851 t6989586621680450184 :: TyFun (t6989586621680450184 a6989586621680450201) Bool -> Type)
type Apply (NotElemSym0 :: TyFun a6989586621680450095 (t6989586621680450094 a6989586621680450095 ~> Bool) -> Type) (a6989586621680450577 :: a6989586621680450095) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (NotElemSym0 :: TyFun a6989586621680450095 (t6989586621680450094 a6989586621680450095 ~> Bool) -> Type) (a6989586621680450577 :: a6989586621680450095) = (NotElemSym1 a6989586621680450577 t6989586621680450094 :: TyFun (t6989586621680450094 a6989586621680450095) Bool -> Type)
type Apply (Elem_6989586621680451233Sym0 :: TyFun a6989586621680450201 (t6989586621680450184 a6989586621680450201 ~> Bool) -> Type) (a6989586621680451231 :: a6989586621680450201) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680451233Sym0 :: TyFun a6989586621680450201 (t6989586621680450184 a6989586621680450201 ~> Bool) -> Type) (a6989586621680451231 :: a6989586621680450201) = (Elem_6989586621680451233Sym1 a6989586621680451231 t6989586621680450184 :: TyFun (t6989586621680450184 a6989586621680450201) Bool -> Type)
type Apply (Elem_6989586621680451570Sym0 :: TyFun a6989586621680450201 (t6989586621680450184 a6989586621680450201 ~> Bool) -> Type) (a6989586621680451568 :: a6989586621680450201) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680451570Sym0 :: TyFun a6989586621680450201 (t6989586621680450184 a6989586621680450201 ~> Bool) -> Type) (a6989586621680451568 :: a6989586621680450201) = (Elem_6989586621680451570Sym1 a6989586621680451568 t6989586621680450184 :: TyFun (t6989586621680450184 a6989586621680450201) Bool -> Type)
type Apply (Elem_6989586621680451737Sym0 :: TyFun a6989586621680450201 (t6989586621680450184 a6989586621680450201 ~> Bool) -> Type) (a6989586621680451735 :: a6989586621680450201) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680451737Sym0 :: TyFun a6989586621680450201 (t6989586621680450184 a6989586621680450201 ~> Bool) -> Type) (a6989586621680451735 :: a6989586621680450201) = (Elem_6989586621680451737Sym1 a6989586621680451735 t6989586621680450184 :: TyFun (t6989586621680450184 a6989586621680450201) Bool -> Type)
type Apply (Elem_6989586621680451904Sym0 :: TyFun a6989586621680450201 (t6989586621680450184 a6989586621680450201 ~> Bool) -> Type) (a6989586621680451902 :: a6989586621680450201) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680451904Sym0 :: TyFun a6989586621680450201 (t6989586621680450184 a6989586621680450201 ~> Bool) -> Type) (a6989586621680451902 :: a6989586621680450201) = (Elem_6989586621680451904Sym1 a6989586621680451902 t6989586621680450184 :: TyFun (t6989586621680450184 a6989586621680450201) Bool -> Type)
type Apply (Let6989586621679948426Scrutinee_6989586621679939829Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (x6989586621679948423 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948426Scrutinee_6989586621679939829Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (x6989586621679948423 :: k1) = (Let6989586621679948426Scrutinee_6989586621679939829Sym1 x6989586621679948423 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type)
type Apply (Let6989586621679948507Scrutinee_6989586621679939823Sym0 :: TyFun k1 (TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) (key6989586621679948503 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948507Scrutinee_6989586621679939823Sym0 :: TyFun k1 (TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) (key6989586621679948503 :: k1) = (Let6989586621679948507Scrutinee_6989586621679939823Sym1 key6989586621679948503 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type)
type Apply (Let6989586621679948522Scrutinee_6989586621679939813Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (n6989586621679948519 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948522Scrutinee_6989586621679939813Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (n6989586621679948519 :: k1) = (Let6989586621679948522Scrutinee_6989586621679939813Sym1 n6989586621679948519 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type)
type Apply (Let6989586621679948536Scrutinee_6989586621679939811Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (n6989586621679948533 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948536Scrutinee_6989586621679939811Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (n6989586621679948533 :: k1) = (Let6989586621679948536Scrutinee_6989586621679939811Sym1 n6989586621679948533 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type)
type Apply (Let6989586621679949118Scrutinee_6989586621679939831Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun [k2] Bool -> Type) -> Type) -> Type) -> Type) (l6989586621679949108 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679949118Scrutinee_6989586621679939831Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun [k2] Bool -> Type) -> Type) -> Type) -> Type) (l6989586621679949108 :: k1) = (Let6989586621679949118Scrutinee_6989586621679939831Sym1 l6989586621679949108 :: TyFun k2 (TyFun k3 (TyFun [k2] Bool -> Type) -> Type) -> Type)
type Apply (Lambda_6989586621680451060Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (a_69895866216804510556989586621680451059 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Lambda_6989586621680451060Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (a_69895866216804510556989586621680451059 :: k1) = (Lambda_6989586621680451060Sym1 a_69895866216804510556989586621680451059 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type)
type Apply (Let6989586621679949737Scrutinee_6989586621679939805Sym1 p6989586621679949731 :: TyFun k1 (TyFun [a6989586621679939246] (TyFun k Bool -> Type) -> Type) -> Type) (x6989586621679949735 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679949737Scrutinee_6989586621679939805Sym1 p6989586621679949731 :: TyFun k1 (TyFun [a6989586621679939246] (TyFun k Bool -> Type) -> Type) -> Type) (x6989586621679949735 :: k1) = (Let6989586621679949737Scrutinee_6989586621679939805Sym2 p6989586621679949731 x6989586621679949735 :: TyFun [a6989586621679939246] (TyFun k Bool -> Type) -> Type)
type Apply (Let6989586621679948426Scrutinee_6989586621679939829Sym1 x6989586621679948423 :: TyFun k1 (TyFun k3 Bool -> Type) -> Type) (xs6989586621679948424 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948426Scrutinee_6989586621679939829Sym1 x6989586621679948423 :: TyFun k1 (TyFun k3 Bool -> Type) -> Type) (xs6989586621679948424 :: k1) = (Let6989586621679948426Scrutinee_6989586621679939829Sym2 x6989586621679948423 xs6989586621679948424 :: TyFun k3 Bool -> Type)
type Apply (Let6989586621679948507Scrutinee_6989586621679939823Sym1 key6989586621679948503 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (x6989586621679948504 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948507Scrutinee_6989586621679939823Sym1 key6989586621679948503 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (x6989586621679948504 :: k1) = (Let6989586621679948507Scrutinee_6989586621679939823Sym2 key6989586621679948503 x6989586621679948504 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type)
type Apply (Let6989586621679948522Scrutinee_6989586621679939813Sym1 n6989586621679948519 :: TyFun k1 (TyFun k3 Bool -> Type) -> Type) (x6989586621679948520 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948522Scrutinee_6989586621679939813Sym1 n6989586621679948519 :: TyFun k1 (TyFun k3 Bool -> Type) -> Type) (x6989586621679948520 :: k1) = (Let6989586621679948522Scrutinee_6989586621679939813Sym2 n6989586621679948519 x6989586621679948520 :: TyFun k3 Bool -> Type)
type Apply (Let6989586621679948536Scrutinee_6989586621679939811Sym1 n6989586621679948533 :: TyFun k1 (TyFun k3 Bool -> Type) -> Type) (x6989586621679948534 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948536Scrutinee_6989586621679939811Sym1 n6989586621679948533 :: TyFun k1 (TyFun k3 Bool -> Type) -> Type) (x6989586621679948534 :: k1) = (Let6989586621679948536Scrutinee_6989586621679939811Sym2 n6989586621679948533 x6989586621679948534 :: TyFun k3 Bool -> Type)
type Apply (Let6989586621679948410Scrutinee_6989586621679939833Sym1 eq6989586621679948398 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun [k2] Bool -> Type) -> Type) -> Type) -> Type) (l6989586621679948399 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948410Scrutinee_6989586621679939833Sym1 eq6989586621679948398 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun [k2] Bool -> Type) -> Type) -> Type) -> Type) (l6989586621679948399 :: k1) = (Let6989586621679948410Scrutinee_6989586621679939833Sym2 eq6989586621679948398 l6989586621679948399 :: TyFun k2 (TyFun k3 (TyFun [k2] Bool -> Type) -> Type) -> Type)
type Apply (Let6989586621679949118Scrutinee_6989586621679939831Sym1 l6989586621679949108 :: TyFun k1 (TyFun k3 (TyFun [k1] Bool -> Type) -> Type) -> Type) (x6989586621679949115 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679949118Scrutinee_6989586621679939831Sym1 l6989586621679949108 :: TyFun k1 (TyFun k3 (TyFun [k1] Bool -> Type) -> Type) -> Type) (x6989586621679949115 :: k1) = (Let6989586621679949118Scrutinee_6989586621679939831Sym2 l6989586621679949108 x6989586621679949115 :: TyFun k3 (TyFun [k1] Bool -> Type) -> Type)
type Apply (Lambda_6989586621680451060Sym1 a_69895866216804510556989586621680451059 :: TyFun k1 (TyFun k3 Bool -> Type) -> Type) (t6989586621680451067 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Lambda_6989586621680451060Sym1 a_69895866216804510556989586621680451059 :: TyFun k1 (TyFun k3 Bool -> Type) -> Type) (t6989586621680451067 :: k1) = (Lambda_6989586621680451060Sym2 a_69895866216804510556989586621680451059 t6989586621680451067 :: TyFun k3 Bool -> Type)
type Apply (Let6989586621679739600Scrutinee_6989586621679739366Sym0 :: TyFun k1 (TyFun k2 (TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (x06989586621679739590 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621679739600Scrutinee_6989586621679739366Sym0 :: TyFun k1 (TyFun k2 (TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (x06989586621679739590 :: k1) = (Let6989586621679739600Scrutinee_6989586621679739366Sym1 x06989586621679739590 :: TyFun k2 (TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type)
type Apply (Let6989586621679949118Scrutinee_6989586621679939831Sym2 x6989586621679949115 l6989586621679949108 :: TyFun k3 (TyFun [k1] Bool -> Type) -> Type) (xs6989586621679949116 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679949118Scrutinee_6989586621679939831Sym2 x6989586621679949115 l6989586621679949108 :: TyFun k3 (TyFun [k1] Bool -> Type) -> Type) (xs6989586621679949116 :: k3) = Let6989586621679949118Scrutinee_6989586621679939831Sym3 x6989586621679949115 l6989586621679949108 xs6989586621679949116
type Apply (Let6989586621679948507Scrutinee_6989586621679939823Sym2 x6989586621679948504 key6989586621679948503 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) (y6989586621679948505 :: k2) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948507Scrutinee_6989586621679939823Sym2 x6989586621679948504 key6989586621679948503 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) (y6989586621679948505 :: k2) = (Let6989586621679948507Scrutinee_6989586621679939823Sym3 x6989586621679948504 key6989586621679948503 y6989586621679948505 :: TyFun k3 Bool -> Type)
type Apply (Let6989586621679948410Scrutinee_6989586621679939833Sym2 l6989586621679948399 eq6989586621679948398 :: TyFun k2 (TyFun k3 (TyFun [k2] Bool -> Type) -> Type) -> Type) (y6989586621679948407 :: k2) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948410Scrutinee_6989586621679939833Sym2 l6989586621679948399 eq6989586621679948398 :: TyFun k2 (TyFun k3 (TyFun [k2] Bool -> Type) -> Type) -> Type) (y6989586621679948407 :: k2) = (Let6989586621679948410Scrutinee_6989586621679939833Sym3 l6989586621679948399 eq6989586621679948398 y6989586621679948407 :: TyFun k3 (TyFun [k2] Bool -> Type) -> Type)
type Apply (Let6989586621679739466Scrutinee_6989586621679739390Sym0 :: TyFun k1 (TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (x16989586621679739461 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621679739466Scrutinee_6989586621679739390Sym0 :: TyFun k1 (TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (x16989586621679739461 :: k1) = (Let6989586621679739466Scrutinee_6989586621679739390Sym1 x16989586621679739461 :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type)
type Apply (Let6989586621679739523Scrutinee_6989586621679739380Sym0 :: TyFun k1 (TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (x16989586621679739518 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621679739523Scrutinee_6989586621679739380Sym0 :: TyFun k1 (TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (x16989586621679739518 :: k1) = (Let6989586621679739523Scrutinee_6989586621679739380Sym1 x16989586621679739518 :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type)
type Apply (Let6989586621679739600Scrutinee_6989586621679739366Sym1 x06989586621679739590 :: TyFun k1 (TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) (y6989586621679739591 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621679739600Scrutinee_6989586621679739366Sym1 x06989586621679739590 :: TyFun k1 (TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) (y6989586621679739591 :: k1) = (Let6989586621679739600Scrutinee_6989586621679739366Sym2 x06989586621679739590 y6989586621679739591 :: TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type)
type Apply (Let6989586621679948410Scrutinee_6989586621679939833Sym3 y6989586621679948407 l6989586621679948399 eq6989586621679948398 :: TyFun k3 (TyFun [k2] Bool -> Type) -> Type) (ys6989586621679948408 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948410Scrutinee_6989586621679939833Sym3 y6989586621679948407 l6989586621679948399 eq6989586621679948398 :: TyFun k3 (TyFun [k2] Bool -> Type) -> Type) (ys6989586621679948408 :: k3) = Let6989586621679948410Scrutinee_6989586621679939833Sym4 y6989586621679948407 l6989586621679948399 eq6989586621679948398 ys6989586621679948408
type Apply (Let6989586621679739466Scrutinee_6989586621679739390Sym1 x16989586621679739461 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (x26989586621679739462 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621679739466Scrutinee_6989586621679739390Sym1 x16989586621679739461 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (x26989586621679739462 :: k1) = (Let6989586621679739466Scrutinee_6989586621679739390Sym2 x16989586621679739461 x26989586621679739462 :: TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type)
type Apply (Let6989586621679739523Scrutinee_6989586621679739380Sym1 x16989586621679739518 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (x26989586621679739519 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621679739523Scrutinee_6989586621679739380Sym1 x16989586621679739518 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (x26989586621679739519 :: k1) = (Let6989586621679739523Scrutinee_6989586621679739380Sym2 x16989586621679739518 x26989586621679739519 :: TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type)
type Apply (Let6989586621679739600Scrutinee_6989586621679739366Sym2 y6989586621679739591 x06989586621679739590 :: TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) (x6989586621679739599 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621679739600Scrutinee_6989586621679739366Sym2 y6989586621679739591 x06989586621679739590 :: TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) (x6989586621679739599 :: k1) = (Let6989586621679739600Scrutinee_6989586621679739366Sym3 y6989586621679739591 x06989586621679739590 x6989586621679739599 :: TyFun k3 (TyFun k4 Bool -> Type) -> Type)
type Apply (Let6989586621679739466Scrutinee_6989586621679739390Sym2 x26989586621679739462 x16989586621679739461 :: TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) (y6989586621679739463 :: k2) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621679739466Scrutinee_6989586621679739390Sym2 x26989586621679739462 x16989586621679739461 :: TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) (y6989586621679739463 :: k2) = (Let6989586621679739466Scrutinee_6989586621679739390Sym3 x26989586621679739462 x16989586621679739461 y6989586621679739463 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type)
type Apply (Let6989586621679739523Scrutinee_6989586621679739380Sym2 x26989586621679739519 x16989586621679739518 :: TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) (y6989586621679739520 :: k2) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621679739523Scrutinee_6989586621679739380Sym2 x26989586621679739519 x16989586621679739518 :: TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) (y6989586621679739520 :: k2) = (Let6989586621679739523Scrutinee_6989586621679739380Sym3 x26989586621679739519 x16989586621679739518 y6989586621679739520 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type)
type Apply (Let6989586621679739600Scrutinee_6989586621679739366Sym3 x6989586621679739599 y6989586621679739591 x06989586621679739590 :: TyFun k3 (TyFun k4 Bool -> Type) -> Type) (arg_69895866216797393626989586621679739586 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621679739600Scrutinee_6989586621679739366Sym3 x6989586621679739599 y6989586621679739591 x06989586621679739590 :: TyFun k3 (TyFun k4 Bool -> Type) -> Type) (arg_69895866216797393626989586621679739586 :: k3) = (Let6989586621679739600Scrutinee_6989586621679739366Sym4 x6989586621679739599 y6989586621679739591 x06989586621679739590 arg_69895866216797393626989586621679739586 :: TyFun k4 Bool -> Type)
type Apply (Let6989586621679739466Scrutinee_6989586621679739390Sym3 y6989586621679739463 x26989586621679739462 x16989586621679739461 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) (arg_69895866216797393846989586621679739456 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621679739466Scrutinee_6989586621679739390Sym3 y6989586621679739463 x26989586621679739462 x16989586621679739461 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) (arg_69895866216797393846989586621679739456 :: k3) = (Let6989586621679739466Scrutinee_6989586621679739390Sym4 y6989586621679739463 x26989586621679739462 x16989586621679739461 arg_69895866216797393846989586621679739456 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type)
type Apply (Let6989586621679739523Scrutinee_6989586621679739380Sym3 y6989586621679739520 x26989586621679739519 x16989586621679739518 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) (arg_69895866216797393746989586621679739513 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621679739523Scrutinee_6989586621679739380Sym3 y6989586621679739520 x26989586621679739519 x16989586621679739518 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) (arg_69895866216797393746989586621679739513 :: k3) = (Let6989586621679739523Scrutinee_6989586621679739380Sym4 y6989586621679739520 x26989586621679739519 x16989586621679739518 arg_69895866216797393746989586621679739513 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type)
type Apply (Let6989586621679739466Scrutinee_6989586621679739390Sym4 arg_69895866216797393846989586621679739456 y6989586621679739463 x26989586621679739462 x16989586621679739461 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type) (arg_69895866216797393866989586621679739457 :: k4) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621679739466Scrutinee_6989586621679739390Sym4 arg_69895866216797393846989586621679739456 y6989586621679739463 x26989586621679739462 x16989586621679739461 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type) (arg_69895866216797393866989586621679739457 :: k4) = (Let6989586621679739466Scrutinee_6989586621679739390Sym5 arg_69895866216797393846989586621679739456 y6989586621679739463 x26989586621679739462 x16989586621679739461 arg_69895866216797393866989586621679739457 :: TyFun k5 Bool -> Type)
type Apply (Let6989586621679739523Scrutinee_6989586621679739380Sym4 arg_69895866216797393746989586621679739513 y6989586621679739520 x26989586621679739519 x16989586621679739518 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type) (arg_69895866216797393766989586621679739514 :: k4) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621679739523Scrutinee_6989586621679739380Sym4 arg_69895866216797393746989586621679739513 y6989586621679739520 x26989586621679739519 x16989586621679739518 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type) (arg_69895866216797393766989586621679739514 :: k4) = (Let6989586621679739523Scrutinee_6989586621679739380Sym5 arg_69895866216797393746989586621679739513 y6989586621679739520 x26989586621679739519 x16989586621679739518 arg_69895866216797393766989586621679739514 :: TyFun k5 Bool -> Type)
type Apply (ListisPrefixOfSym0 :: TyFun [a6989586621680386731] ([a6989586621680386731] ~> Bool) -> Type) (a6989586621680387783 :: [a6989586621680386731]) 
Instance details

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

type Apply (ListisPrefixOfSym0 :: TyFun [a6989586621680386731] ([a6989586621680386731] ~> Bool) -> Type) (a6989586621680387783 :: [a6989586621680386731]) = ListisPrefixOfSym1 a6989586621680387783
type Apply (IsPrefixOfSym0 :: TyFun [a6989586621679939212] ([a6989586621679939212] ~> Bool) -> Type) (a6989586621679949126 :: [a6989586621679939212]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IsPrefixOfSym0 :: TyFun [a6989586621679939212] ([a6989586621679939212] ~> Bool) -> Type) (a6989586621679949126 :: [a6989586621679939212]) = IsPrefixOfSym1 a6989586621679949126
type Apply (IsInfixOfSym0 :: TyFun [a6989586621679939210] ([a6989586621679939210] ~> Bool) -> Type) (a6989586621679949364 :: [a6989586621679939210]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IsInfixOfSym0 :: TyFun [a6989586621679939210] ([a6989586621679939210] ~> Bool) -> Type) (a6989586621679949364 :: [a6989586621679939210]) = IsInfixOfSym1 a6989586621679949364
type Apply (IsSuffixOfSym0 :: TyFun [a6989586621679939211] ([a6989586621679939211] ~> Bool) -> Type) (a6989586621679949717 :: [a6989586621679939211]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IsSuffixOfSym0 :: TyFun [a6989586621679939211] ([a6989586621679939211] ~> Bool) -> Type) (a6989586621679949717 :: [a6989586621679939211]) = IsSuffixOfSym1 a6989586621679949717
type Apply (Let6989586621679949737Scrutinee_6989586621679939805Sym2 x6989586621679949735 p6989586621679949731 :: TyFun [a6989586621679939246] (TyFun k Bool -> Type) -> Type) (xs6989586621679949736 :: [a6989586621679939246]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679949737Scrutinee_6989586621679939805Sym2 x6989586621679949735 p6989586621679949731 :: TyFun [a6989586621679939246] (TyFun k Bool -> Type) -> Type) (xs6989586621679949736 :: [a6989586621679939246]) = (Let6989586621679949737Scrutinee_6989586621679939805Sym3 x6989586621679949735 p6989586621679949731 xs6989586621679949736 :: TyFun k Bool -> Type)
type Apply (Let6989586621679948567ZsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621679948554 :: k ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948567ZsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621679948554 :: k ~> Bool) = Let6989586621679948567ZsSym1 p6989586621679948554
type Apply (Let6989586621679948567YsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621679948554 :: k ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948567YsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621679948554 :: k ~> Bool) = Let6989586621679948567YsSym1 p6989586621679948554
type Apply (Let6989586621679948567X_6989586621679948568Sym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] ([k], [k]) -> Type) -> Type) -> Type) (p6989586621679948554 :: k ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948567X_6989586621679948568Sym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] ([k], [k]) -> Type) -> Type) -> Type) (p6989586621679948554 :: k ~> Bool) = Let6989586621679948567X_6989586621679948568Sym1 p6989586621679948554
type Apply (Let6989586621679948610ZsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621679948597 :: k ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948610ZsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621679948597 :: k ~> Bool) = Let6989586621679948610ZsSym1 p6989586621679948597
type Apply (Let6989586621679948610YsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621679948597 :: k ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948610YsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621679948597 :: k ~> Bool) = Let6989586621679948610YsSym1 p6989586621679948597
type Apply (Let6989586621679948610X_6989586621679948611Sym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] ([k], [k]) -> Type) -> Type) -> Type) (p6989586621679948597 :: k ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948610X_6989586621679948611Sym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] ([k], [k]) -> Type) -> Type) -> Type) (p6989586621679948597 :: k ~> Bool) = Let6989586621679948610X_6989586621679948611Sym1 p6989586621679948597
type Apply (ListnubBySym0 :: TyFun (a6989586621680386725 ~> (a6989586621680386725 ~> Bool)) ([a6989586621680386725] ~> [a6989586621680386725]) -> Type) (a6989586621680387748 :: a6989586621680386725 ~> (a6989586621680386725 ~> Bool)) 
Instance details

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

type Apply (ListnubBySym0 :: TyFun (a6989586621680386725 ~> (a6989586621680386725 ~> Bool)) ([a6989586621680386725] ~> [a6989586621680386725]) -> Type) (a6989586621680387748 :: a6989586621680386725 ~> (a6989586621680386725 ~> Bool)) = ListnubBySym1 a6989586621680387748
type Apply (ListpartitionSym0 :: TyFun (a6989586621680386733 ~> Bool) ([a6989586621680386733] ~> ([a6989586621680386733], [a6989586621680386733])) -> Type) (a6989586621680387803 :: a6989586621680386733 ~> Bool) 
Instance details

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

type Apply (ListpartitionSym0 :: TyFun (a6989586621680386733 ~> Bool) ([a6989586621680386733] ~> ([a6989586621680386733], [a6989586621680386733])) -> Type) (a6989586621680387803 :: a6989586621680386733 ~> Bool) = ListpartitionSym1 a6989586621680387803
type Apply (ListfilterSym0 :: TyFun (a6989586621680386734 ~> Bool) ([a6989586621680386734] ~> [a6989586621680386734]) -> Type) (a6989586621680387813 :: a6989586621680386734 ~> Bool) 
Instance details

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

type Apply (ListfilterSym0 :: TyFun (a6989586621680386734 ~> Bool) ([a6989586621680386734] ~> [a6989586621680386734]) -> Type) (a6989586621680387813 :: a6989586621680386734 ~> Bool) = ListfilterSym1 a6989586621680387813
type Apply (ListspanSym0 :: TyFun (a6989586621680386735 ~> Bool) ([a6989586621680386735] ~> ([a6989586621680386735], [a6989586621680386735])) -> Type) (a6989586621680387823 :: a6989586621680386735 ~> Bool) 
Instance details

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

type Apply (ListspanSym0 :: TyFun (a6989586621680386735 ~> Bool) ([a6989586621680386735] ~> ([a6989586621680386735], [a6989586621680386735])) -> Type) (a6989586621680387823 :: a6989586621680386735 ~> Bool) = ListspanSym1 a6989586621680387823
type Apply (ListdropWhileSym0 :: TyFun (a6989586621680386736 ~> Bool) ([a6989586621680386736] ~> [a6989586621680386736]) -> Type) (a6989586621680387833 :: a6989586621680386736 ~> Bool) 
Instance details

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

type Apply (ListdropWhileSym0 :: TyFun (a6989586621680386736 ~> Bool) ([a6989586621680386736] ~> [a6989586621680386736]) -> Type) (a6989586621680387833 :: a6989586621680386736 ~> Bool) = ListdropWhileSym1 a6989586621680387833
type Apply (ListtakeWhileSym0 :: TyFun (a6989586621680386737 ~> Bool) ([a6989586621680386737] ~> [a6989586621680386737]) -> Type) (a6989586621680387843 :: a6989586621680386737 ~> Bool) 
Instance details

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

type Apply (ListtakeWhileSym0 :: TyFun (a6989586621680386737 ~> Bool) ([a6989586621680386737] ~> [a6989586621680386737]) -> Type) (a6989586621680387843 :: a6989586621680386737 ~> Bool) = ListtakeWhileSym1 a6989586621680387843
type Apply (NubBySym0 :: TyFun (a6989586621679939127 ~> (a6989586621679939127 ~> Bool)) ([a6989586621679939127] ~> [a6989586621679939127]) -> Type) (a6989586621679948394 :: a6989586621679939127 ~> (a6989586621679939127 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (NubBySym0 :: TyFun (a6989586621679939127 ~> (a6989586621679939127 ~> Bool)) ([a6989586621679939127] ~> [a6989586621679939127]) -> Type) (a6989586621679948394 :: a6989586621679939127 ~> (a6989586621679939127 ~> Bool)) = NubBySym1 a6989586621679948394
type Apply (PartitionSym0 :: TyFun (a6989586621679939136 ~> Bool) ([a6989586621679939136] ~> ([a6989586621679939136], [a6989586621679939136])) -> Type) (a6989586621679948492 :: a6989586621679939136 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (PartitionSym0 :: TyFun (a6989586621679939136 ~> Bool) ([a6989586621679939136] ~> ([a6989586621679939136], [a6989586621679939136])) -> Type) (a6989586621679948492 :: a6989586621679939136 ~> Bool) = PartitionSym1 a6989586621679948492
type Apply (BreakSym0 :: TyFun (a6989586621679939148 ~> Bool) ([a6989586621679939148] ~> ([a6989586621679939148], [a6989586621679939148])) -> Type) (a6989586621679948549 :: a6989586621679939148 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (BreakSym0 :: TyFun (a6989586621679939148 ~> Bool) ([a6989586621679939148] ~> ([a6989586621679939148], [a6989586621679939148])) -> Type) (a6989586621679948549 :: a6989586621679939148 ~> Bool) = BreakSym1 a6989586621679948549
type Apply (SpanSym0 :: TyFun (a6989586621679939149 ~> Bool) ([a6989586621679939149] ~> ([a6989586621679939149], [a6989586621679939149])) -> Type) (a6989586621679948592 :: a6989586621679939149 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (SpanSym0 :: TyFun (a6989586621679939149 ~> Bool) ([a6989586621679939149] ~> ([a6989586621679939149], [a6989586621679939149])) -> Type) (a6989586621679948592 :: a6989586621679939149 ~> Bool) = SpanSym1 a6989586621679948592
type Apply (GroupBySym0 :: TyFun (a6989586621679939139 ~> (a6989586621679939139 ~> Bool)) ([a6989586621679939139] ~> [[a6989586621679939139]]) -> Type) (a6989586621679948635 :: a6989586621679939139 ~> (a6989586621679939139 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (GroupBySym0 :: TyFun (a6989586621679939139 ~> (a6989586621679939139 ~> Bool)) ([a6989586621679939139] ~> [[a6989586621679939139]]) -> Type) (a6989586621679948635 :: a6989586621679939139 ~> (a6989586621679939139 ~> Bool)) = GroupBySym1 a6989586621679948635
type Apply (DropWhileSym0 :: TyFun (a6989586621679939151 ~> Bool) ([a6989586621679939151] ~> [a6989586621679939151]) -> Type) (a6989586621679948669 :: a6989586621679939151 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DropWhileSym0 :: TyFun (a6989586621679939151 ~> Bool) ([a6989586621679939151] ~> [a6989586621679939151]) -> Type) (a6989586621679948669 :: a6989586621679939151 ~> Bool) = DropWhileSym1 a6989586621679948669
type Apply (TakeWhileSym0 :: TyFun (a6989586621679939152 ~> Bool) ([a6989586621679939152] ~> [a6989586621679939152]) -> Type) (a6989586621679948687 :: a6989586621679939152 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (TakeWhileSym0 :: TyFun (a6989586621679939152 ~> Bool) ([a6989586621679939152] ~> [a6989586621679939152]) -> Type) (a6989586621679948687 :: a6989586621679939152 ~> Bool) = TakeWhileSym1 a6989586621679948687
type Apply (FilterSym0 :: TyFun (a6989586621679939160 ~> Bool) ([a6989586621679939160] ~> [a6989586621679939160]) -> Type) (a6989586621679948701 :: a6989586621679939160 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FilterSym0 :: TyFun (a6989586621679939160 ~> Bool) ([a6989586621679939160] ~> [a6989586621679939160]) -> Type) (a6989586621679948701 :: a6989586621679939160 ~> Bool) = FilterSym1 a6989586621679948701
type Apply (FindSym0 :: TyFun (a6989586621679939159 ~> Bool) ([a6989586621679939159] ~> Maybe a6989586621679939159) -> Type) (a6989586621679948716 :: a6989586621679939159 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FindSym0 :: TyFun (a6989586621679939159 ~> Bool) ([a6989586621679939159] ~> Maybe a6989586621679939159) -> Type) (a6989586621679948716 :: a6989586621679939159 ~> Bool) = FindSym1 a6989586621679948716
type Apply (DeleteFirstsBySym0 :: TyFun (a6989586621679939165 ~> (a6989586621679939165 ~> Bool)) ([a6989586621679939165] ~> ([a6989586621679939165] ~> [a6989586621679939165])) -> Type) (a6989586621679948785 :: a6989586621679939165 ~> (a6989586621679939165 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DeleteFirstsBySym0 :: TyFun (a6989586621679939165 ~> (a6989586621679939165 ~> Bool)) ([a6989586621679939165] ~> ([a6989586621679939165] ~> [a6989586621679939165])) -> Type) (a6989586621679948785 :: a6989586621679939165 ~> (a6989586621679939165 ~> Bool)) = DeleteFirstsBySym1 a6989586621679948785
type Apply (UnionBySym0 :: TyFun (a6989586621679939125 ~> (a6989586621679939125 ~> Bool)) ([a6989586621679939125] ~> ([a6989586621679939125] ~> [a6989586621679939125])) -> Type) (a6989586621679948798 :: a6989586621679939125 ~> (a6989586621679939125 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (UnionBySym0 :: TyFun (a6989586621679939125 ~> (a6989586621679939125 ~> Bool)) ([a6989586621679939125] ~> ([a6989586621679939125] ~> [a6989586621679939125])) -> Type) (a6989586621679948798 :: a6989586621679939125 ~> (a6989586621679939125 ~> Bool)) = UnionBySym1 a6989586621679948798
type Apply (FindIndicesSym0 :: TyFun (a6989586621679939155 ~> Bool) ([a6989586621679939155] ~> [Nat]) -> Type) (a6989586621679949042 :: a6989586621679939155 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FindIndicesSym0 :: TyFun (a6989586621679939155 ~> Bool) ([a6989586621679939155] ~> [Nat]) -> Type) (a6989586621679949042 :: a6989586621679939155 ~> Bool) = FindIndicesSym1 a6989586621679949042
type Apply (FindIndexSym0 :: TyFun (a6989586621679939156 ~> Bool) ([a6989586621679939156] ~> Maybe Nat) -> Type) (a6989586621679949076 :: a6989586621679939156 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FindIndexSym0 :: TyFun (a6989586621679939156 ~> Bool) ([a6989586621679939156] ~> Maybe Nat) -> Type) (a6989586621679949076 :: a6989586621679939156 ~> Bool) = FindIndexSym1 a6989586621679949076
type Apply (AnySym0 :: TyFun (a6989586621679939229 ~> Bool) ([a6989586621679939229] ~> Bool) -> Type) (a6989586621679949357 :: a6989586621679939229 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (AnySym0 :: TyFun (a6989586621679939229 ~> Bool) ([a6989586621679939229] ~> Bool) -> Type) (a6989586621679949357 :: a6989586621679939229 ~> Bool) = AnySym1 a6989586621679949357
type Apply (IntersectBySym0 :: TyFun (a6989586621679939153 ~> (a6989586621679939153 ~> Bool)) ([a6989586621679939153] ~> ([a6989586621679939153] ~> [a6989586621679939153])) -> Type) (a6989586621679949370 :: a6989586621679939153 ~> (a6989586621679939153 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IntersectBySym0 :: TyFun (a6989586621679939153 ~> (a6989586621679939153 ~> Bool)) ([a6989586621679939153] ~> ([a6989586621679939153] ~> [a6989586621679939153])) -> Type) (a6989586621679949370 :: a6989586621679939153 ~> (a6989586621679939153 ~> Bool)) = IntersectBySym1 a6989586621679949370
type Apply (AllSym0 :: TyFun (a6989586621679939230 ~> Bool) ([a6989586621679939230] ~> Bool) -> Type) (a6989586621679949412 :: a6989586621679939230 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (AllSym0 :: TyFun (a6989586621679939230 ~> Bool) ([a6989586621679939230] ~> Bool) -> Type) (a6989586621679949412 :: a6989586621679939230 ~> Bool) = AllSym1 a6989586621679949412
type Apply (DropWhileEndSym0 :: TyFun (a6989586621679939150 ~> Bool) ([a6989586621679939150] ~> [a6989586621679939150]) -> Type) (a6989586621679949725 :: a6989586621679939150 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DropWhileEndSym0 :: TyFun (a6989586621679939150 ~> Bool) ([a6989586621679939150] ~> [a6989586621679939150]) -> Type) (a6989586621679949725 :: a6989586621679939150 ~> Bool) = DropWhileEndSym1 a6989586621679949725
type Apply (Elem_bySym0 :: TyFun (a6989586621679939126 ~> (a6989586621679939126 ~> Bool)) (a6989586621679939126 ~> ([a6989586621679939126] ~> Bool)) -> Type) (a6989586621679948384 :: a6989586621679939126 ~> (a6989586621679939126 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Elem_bySym0 :: TyFun (a6989586621679939126 ~> (a6989586621679939126 ~> Bool)) (a6989586621679939126 ~> ([a6989586621679939126] ~> Bool)) -> Type) (a6989586621679948384 :: a6989586621679939126 ~> (a6989586621679939126 ~> Bool)) = Elem_bySym1 a6989586621679948384
type Apply (SelectSym0 :: TyFun (a6989586621679939135 ~> Bool) (a6989586621679939135 ~> (([a6989586621679939135], [a6989586621679939135]) ~> ([a6989586621679939135], [a6989586621679939135]))) -> Type) (a6989586621679948474 :: a6989586621679939135 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (SelectSym0 :: TyFun (a6989586621679939135 ~> Bool) (a6989586621679939135 ~> (([a6989586621679939135], [a6989586621679939135]) ~> ([a6989586621679939135], [a6989586621679939135]))) -> Type) (a6989586621679948474 :: a6989586621679939135 ~> Bool) = SelectSym1 a6989586621679948474
type Apply (DeleteBySym0 :: TyFun (a6989586621679939166 ~> (a6989586621679939166 ~> Bool)) (a6989586621679939166 ~> ([a6989586621679939166] ~> [a6989586621679939166])) -> Type) (a6989586621679948767 :: a6989586621679939166 ~> (a6989586621679939166 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DeleteBySym0 :: TyFun (a6989586621679939166 ~> (a6989586621679939166 ~> Bool)) (a6989586621679939166 ~> ([a6989586621679939166] ~> [a6989586621679939166])) -> Type) (a6989586621679948767 :: a6989586621679939166 ~> (a6989586621679939166 ~> Bool)) = DeleteBySym1 a6989586621679948767
type Apply (UntilSym0 :: TyFun (a6989586621679519836 ~> Bool) ((a6989586621679519836 ~> a6989586621679519836) ~> (a6989586621679519836 ~> a6989586621679519836)) -> Type) (a6989586621679519961 :: a6989586621679519836 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (UntilSym0 :: TyFun (a6989586621679519836 ~> Bool) ((a6989586621679519836 ~> a6989586621679519836) ~> (a6989586621679519836 ~> a6989586621679519836)) -> Type) (a6989586621679519961 :: a6989586621679519836 ~> Bool) = UntilSym1 a6989586621679519961
type Apply (Let6989586621679948400NubBy'Sym0 :: TyFun (k1 ~> (k1 ~> Bool)) (TyFun k (TyFun [k1] ([k1] ~> [k1]) -> Type) -> Type) -> Type) (eq6989586621679948398 :: k1 ~> (k1 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948400NubBy'Sym0 :: TyFun (k1 ~> (k1 ~> Bool)) (TyFun k (TyFun [k1] ([k1] ~> [k1]) -> Type) -> Type) -> Type) (eq6989586621679948398 :: k1 ~> (k1 ~> Bool)) = (Let6989586621679948400NubBy'Sym1 eq6989586621679948398 :: TyFun k (TyFun [k1] ([k1] ~> [k1]) -> Type) -> Type)
type Apply (Let6989586621679948642ZsSym0 :: TyFun (k1 ~> (a6989586621679939149 ~> Bool)) (TyFun k1 (TyFun [a6989586621679939149] [a6989586621679939149] -> Type) -> Type) -> Type) (eq6989586621679948639 :: k1 ~> (a6989586621679939149 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948642ZsSym0 :: TyFun (k1 ~> (a6989586621679939149 ~> Bool)) (TyFun k1 (TyFun [a6989586621679939149] [a6989586621679939149] -> Type) -> Type) -> Type) (eq6989586621679948639 :: k1 ~> (a6989586621679939149 ~> Bool)) = Let6989586621679948642ZsSym1 eq6989586621679948639
type Apply (Let6989586621679948642YsSym0 :: TyFun (k1 ~> (a6989586621679939149 ~> Bool)) (TyFun k1 (TyFun [a6989586621679939149] [a6989586621679939149] -> Type) -> Type) -> Type) (eq6989586621679948639 :: k1 ~> (a6989586621679939149 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948642YsSym0 :: TyFun (k1 ~> (a6989586621679939149 ~> Bool)) (TyFun k1 (TyFun [a6989586621679939149] [a6989586621679939149] -> Type) -> Type) -> Type) (eq6989586621679948639 :: k1 ~> (a6989586621679939149 ~> Bool)) = Let6989586621679948642YsSym1 eq6989586621679948639
type Apply (Let6989586621679948642X_6989586621679948643Sym0 :: TyFun (k1 ~> (a6989586621679939149 ~> Bool)) (TyFun k1 (TyFun [a6989586621679939149] ([a6989586621679939149], [a6989586621679939149]) -> Type) -> Type) -> Type) (eq6989586621679948639 :: k1 ~> (a6989586621679939149 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948642X_6989586621679948643Sym0 :: TyFun (k1 ~> (a6989586621679939149 ~> Bool)) (TyFun k1 (TyFun [a6989586621679939149] ([a6989586621679939149], [a6989586621679939149]) -> Type) -> Type) -> Type) (eq6989586621679948639 :: k1 ~> (a6989586621679939149 ~> Bool)) = Let6989586621679948642X_6989586621679948643Sym1 eq6989586621679948639
type Apply (Lambda_6989586621679949733Sym0 :: TyFun (a6989586621679939246 ~> Bool) (TyFun k (TyFun a6989586621679939246 (TyFun [a6989586621679939246] [a6989586621679939246] -> Type) -> Type) -> Type) -> Type) (p6989586621679949731 :: a6989586621679939246 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Lambda_6989586621679949733Sym0 :: TyFun (a6989586621679939246 ~> Bool) (TyFun k (TyFun a6989586621679939246 (TyFun [a6989586621679939246] [a6989586621679939246] -> Type) -> Type) -> Type) -> Type) (p6989586621679949731 :: a6989586621679939246 ~> Bool) = (Lambda_6989586621679949733Sym1 p6989586621679949731 :: TyFun k (TyFun a6989586621679939246 (TyFun [a6989586621679939246] [a6989586621679939246] -> Type) -> Type) -> Type)
type Apply (Lambda_6989586621680450557Sym0 :: TyFun (a6989586621679072630 ~> Bool) (TyFun k (TyFun a6989586621679072630 (First a6989586621679072630) -> Type) -> Type) -> Type) (p6989586621680450554 :: a6989586621679072630 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Lambda_6989586621680450557Sym0 :: TyFun (a6989586621679072630 ~> Bool) (TyFun k (TyFun a6989586621679072630 (First a6989586621679072630) -> Type) -> Type) -> Type) (p6989586621680450554 :: a6989586621679072630 ~> Bool) = (Lambda_6989586621680450557Sym1 p6989586621680450554 :: TyFun k (TyFun a6989586621679072630 (First a6989586621679072630) -> Type) -> Type)
type Apply (Let6989586621680450654Scrutinee_6989586621680450435Sym0 :: TyFun (a6989586621680450187 ~> Bool) (TyFun (t6989586621680450184 a6989586621680450187) Any -> Type) -> Type) (p6989586621680450652 :: a6989586621680450187 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680450654Scrutinee_6989586621680450435Sym0 :: TyFun (a6989586621680450187 ~> Bool) (TyFun (t6989586621680450184 a6989586621680450187) Any -> Type) -> Type) (p6989586621680450652 :: a6989586621680450187 ~> Bool) = (Let6989586621680450654Scrutinee_6989586621680450435Sym1 p6989586621680450652 :: TyFun (t6989586621680450184 a6989586621680450187) Any -> Type)
type Apply (Let6989586621680450641Scrutinee_6989586621680450437Sym0 :: TyFun (a6989586621680450187 ~> Bool) (TyFun (t6989586621680450184 a6989586621680450187) All -> Type) -> Type) (p6989586621680450639 :: a6989586621680450187 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680450641Scrutinee_6989586621680450437Sym0 :: TyFun (a6989586621680450187 ~> Bool) (TyFun (t6989586621680450184 a6989586621680450187) All -> Type) -> Type) (p6989586621680450639 :: a6989586621680450187 ~> Bool) = (Let6989586621680450641Scrutinee_6989586621680450437Sym1 p6989586621680450639 :: TyFun (t6989586621680450184 a6989586621680450187) All -> Type)
type Apply (Let6989586621680450556Scrutinee_6989586621680450443Sym0 :: TyFun (a6989586621680450187 ~> Bool) (TyFun (t6989586621680450184 a6989586621680450187) (First a6989586621680450187) -> Type) -> Type) (p6989586621680450554 :: a6989586621680450187 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680450556Scrutinee_6989586621680450443Sym0 :: TyFun (a6989586621680450187 ~> Bool) (TyFun (t6989586621680450184 a6989586621680450187) (First a6989586621680450187) -> Type) -> Type) (p6989586621680450554 :: a6989586621680450187 ~> Bool) = (Let6989586621680450556Scrutinee_6989586621680450443Sym1 p6989586621680450554 :: TyFun (t6989586621680450184 a6989586621680450187) (First a6989586621680450187) -> Type)
type Apply (Let6989586621679519972GoSym0 :: TyFun (k1 ~> Bool) (TyFun (k1 ~> k1) (TyFun k2 (TyFun k1 k1 -> Type) -> Type) -> Type) -> Type) (p6989586621679519969 :: k1 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (Let6989586621679519972GoSym0 :: TyFun (k1 ~> Bool) (TyFun (k1 ~> k1) (TyFun k2 (TyFun k1 k1 -> Type) -> Type) -> Type) -> Type) (p6989586621679519969 :: k1 ~> Bool) = (Let6989586621679519972GoSym1 p6989586621679519969 :: TyFun (k1 ~> k1) (TyFun k2 (TyFun k1 k1 -> Type) -> Type) -> Type)
type Apply (AnySym0 :: TyFun (a6989586621680450103 ~> Bool) (t6989586621680450102 a6989586621680450103 ~> Bool) -> Type) (a6989586621680450648 :: a6989586621680450103 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AnySym0 :: TyFun (a6989586621680450103 ~> Bool) (t6989586621680450102 a6989586621680450103 ~> Bool) -> Type) (a6989586621680450648 :: a6989586621680450103 ~> Bool) = (AnySym1 a6989586621680450648 t6989586621680450102 :: TyFun (t6989586621680450102 a6989586621680450103) Bool -> Type)
type Apply (AllSym0 :: TyFun (a6989586621680450101 ~> Bool) (t6989586621680450100 a6989586621680450101 ~> Bool) -> Type) (a6989586621680450635 :: a6989586621680450101 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AllSym0 :: TyFun (a6989586621680450101 ~> Bool) (t6989586621680450100 a6989586621680450101 ~> Bool) -> Type) (a6989586621680450635 :: a6989586621680450101 ~> Bool) = (AllSym1 a6989586621680450635 t6989586621680450100 :: TyFun (t6989586621680450100 a6989586621680450101) Bool -> Type)
type Apply (FindSym0 :: TyFun (a6989586621680450093 ~> Bool) (t6989586621680450092 a6989586621680450093 ~> Maybe a6989586621680450093) -> Type) (a6989586621680450550 :: a6989586621680450093 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FindSym0 :: TyFun (a6989586621680450093 ~> Bool) (t6989586621680450092 a6989586621680450093 ~> Maybe a6989586621680450093) -> Type) (a6989586621680450550 :: a6989586621680450093 ~> Bool) = (FindSym1 a6989586621680450550 t6989586621680450092 :: TyFun (t6989586621680450092 a6989586621680450093) (Maybe a6989586621680450093) -> Type)
type Apply (TFHelper_6989586621680882310Sym0 :: TyFun (Arg a6989586621680881093 b6989586621680881094) (Arg a6989586621680881093 b6989586621680881094 ~> Bool) -> Type) (a6989586621680882308 :: Arg a6989586621680881093 b6989586621680881094) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Apply (TFHelper_6989586621680882310Sym0 :: TyFun (Arg a6989586621680881093 b6989586621680881094) (Arg a6989586621680881093 b6989586621680881094 ~> Bool) -> Type) (a6989586621680882308 :: Arg a6989586621680881093 b6989586621680881094) = TFHelper_6989586621680882310Sym1 a6989586621680882308
type Apply (Let6989586621679948410Scrutinee_6989586621679939833Sym0 :: TyFun (k1 ~> (k1 ~> Bool)) (TyFun k2 (TyFun k1 (TyFun k3 (TyFun [k1] Bool -> Type) -> Type) -> Type) -> Type) -> Type) (eq6989586621679948398 :: k1 ~> (k1 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679948410Scrutinee_6989586621679939833Sym0 :: TyFun (k1 ~> (k1 ~> Bool)) (TyFun k2 (TyFun k1 (TyFun k3 (TyFun [k1] Bool -> Type) -> Type) -> Type) -> Type) -> Type) (eq6989586621679948398 :: k1 ~> (k1 ~> Bool)) = (Let6989586621679948410Scrutinee_6989586621679939833Sym1 eq6989586621679948398 :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun [k1] Bool -> Type) -> Type) -> Type) -> Type)
type Apply (Let6989586621679949737Scrutinee_6989586621679939805Sym0 :: TyFun (k1 ~> Bool) (TyFun k1 (TyFun [a6989586621679939246] (TyFun k Bool -> Type) -> Type) -> Type) -> Type) (p6989586621679949731 :: k1 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621679949737Scrutinee_6989586621679939805Sym0 :: TyFun (k1 ~> Bool) (TyFun k1 (TyFun [a6989586621679939246] (TyFun k Bool -> Type) -> Type) -> Type) -> Type) (p6989586621679949731 :: k1 ~> Bool) = (Let6989586621679949737Scrutinee_6989586621679939805Sym1 p6989586621679949731 :: TyFun k1 (TyFun [a6989586621679939246] (TyFun k Bool -> Type) -> Type) -> Type)
type Apply (Lambda_6989586621679949392Sym0 :: TyFun (b6989586621679544160 ~> (a6989586621679939229 ~> Bool)) (TyFun k1 (TyFun k2 (TyFun a6989586621679939229 (TyFun [a6989586621679939229] (TyFun b6989586621679544160 (m6989586621679544156 b6989586621679544160) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (eq6989586621679949376 :: b6989586621679544160 ~> (a6989586621679939229 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Lambda_6989586621679949392Sym0 :: TyFun (b6989586621679544160 ~> (a6989586621679939229 ~> Bool)) (TyFun k1 (TyFun k2 (TyFun a6989586621679939229 (TyFun [a6989586621679939229] (TyFun b6989586621679544160 (m6989586621679544156 b6989586621679544160) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (eq6989586621679949376 :: b6989586621679544160 ~> (a6989586621679939229 ~> Bool)) = (Lambda_6989586621679949392Sym1 eq6989586621679949376 :: TyFun k1 (TyFun k2 (TyFun a6989586621679939229 (TyFun [a6989586621679939229] (TyFun b6989586621679544160 (m6989586621679544156 b6989586621679544160) -> 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 #

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

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

ArithOpHs Compare ByteString ByteString Source # 
Instance details

Defined in Lorentz.Arith

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

type ArithResHs Compare ByteString ByteString Source # 
Instance details

Defined in Lorentz.Arith

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

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToCT Address :: CT Source #

ArithOpHs Compare Address Address Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Compare Address Address :: Type Source #

type ToT Address Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToCT Address Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ArithResHs Compare Address Address Source # 
Instance details

Defined in Lorentz.Arith

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 #

EDivOpHs Mutez Natural Source # 
Instance details

Defined in Lorentz.Polymorphic

EDivOpHs Mutez Mutez Source # 
Instance details

Defined in Lorentz.Polymorphic

ArithOpHs Compare Mutez Mutez Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Compare Mutez Mutez :: 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 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.3.0-7oMtJCcnhvo7MqJS85kloi" 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 Compare Mutez Mutez Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Mul Natural Mutez Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Mul Mutez Natural Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Sub Mutez Mutez Source # 
Instance details

Defined in Lorentz.Arith

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 #

ArithOpHs Compare Timestamp 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.3.0-7oMtJCcnhvo7MqJS85kloi" 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 Compare Timestamp Timestamp Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Sub Timestamp Integer Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Sub Timestamp Timestamp Source # 
Instance details

Defined in Lorentz.Arith

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

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

ArithOpHs Compare KeyHash KeyHash Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Compare KeyHash KeyHash :: Type Source #

type ToT KeyHash Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToCT KeyHash Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ArithResHs Compare KeyHash KeyHash Source # 
Instance details

Defined in Lorentz.Arith

data PublicKey Source #

ED25519 public cryptographic key.

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 #

type ToT PublicKey Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

data Signature Source #

ED25519 cryptographic signature.

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 #

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 #

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 #

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

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

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 #

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 #

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) => FromRecord arity (S1 s (K1 i (Maybe a) :: Type -> Type)) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

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

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

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)

SuppressUnusedWarnings (CatMaybesSym0 :: TyFun [Maybe a6989586621679494598] [a6989586621679494598] -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (ListToMaybeSym0 :: TyFun [a6989586621679494599] (Maybe a6989586621679494599) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (StripPrefixSym0 :: TyFun [a6989586621680065374] ([a6989586621680065374] ~> Maybe [a6989586621680065374]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (MaybeToListSym0 :: TyFun (Maybe a6989586621679494600) [a6989586621679494600] -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

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

Defined in Data.Singletons.Prelude.Maybe

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

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (FromJustSym0 :: TyFun (Maybe a6989586621679494602) a6989586621679494602 -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (TFHelper_6989586621679607586Sym0 :: TyFun (Maybe a6989586621679544211) (Maybe a6989586621679544211 ~> Maybe a6989586621679544211) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (MinInternalSym0 :: TyFun (Maybe a6989586621680441204) (MinInternal a6989586621680441204) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (MaxInternalSym0 :: TyFun (Maybe a6989586621680440525) (MaxInternal a6989586621680440525) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Compare_6989586621679390320Sym0 :: TyFun (Maybe a3530822107858468865) (Maybe a3530822107858468865 ~> Ordering) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (OptionSym0 :: TyFun (Maybe a6989586621679051005) (Option a6989586621679051005) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

SuppressUnusedWarnings (LastSym0 :: TyFun (Maybe a6989586621679072625) (Last a6989586621679072625) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

SuppressUnusedWarnings (FirstSym0 :: TyFun (Maybe a6989586621679072630) (First a6989586621679072630) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

SuppressUnusedWarnings (ShowsPrec_6989586621680280310Sym0 :: TyFun Nat (Maybe a3530822107858468865 ~> (Symbol ~> Symbol)) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings (Fail_6989586621679607493Sym0 :: TyFun Symbol (Maybe a6989586621679544162) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (FromMaybeSym0 :: TyFun a6989586621679494601 (Maybe a6989586621679494601 ~> a6989586621679494601) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (ElemIndexSym0 :: TyFun a6989586621679939158 ([a6989586621679939158] ~> Maybe Nat) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Pure_6989586621679607286Sym0 :: TyFun a6989586621679544133 (Maybe a6989586621679544133) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (Let6989586621679607582LSym0 :: 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 a6989586621679051005) (Maybe a6989586621679051005) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

SuppressUnusedWarnings (GetFirstSym0 :: TyFun (First a6989586621679072630) (Maybe a6989586621679072630) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

SuppressUnusedWarnings (GetLastSym0 :: TyFun (Last a6989586621679072625) (Maybe a6989586621679072625) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (FindIndexSym0 :: TyFun (a6989586621679939156 ~> Bool) ([a6989586621679939156] ~> 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 a6989586621680078084 :: TyFun [a6989586621680065374] (Maybe [a6989586621680065374]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (FindSym1 a6989586621679948716 :: TyFun [a6989586621679939159] (Maybe a6989586621679939159) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (FindIndexSym1 a6989586621679949076 :: TyFun [a6989586621679939156] (Maybe Nat) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (ElemIndexSym1 a6989586621679949084 :: TyFun [a6989586621679939158] (Maybe Nat) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (ShowsPrec_6989586621680280310Sym1 a6989586621680280307 a3530822107858468865 :: TyFun (Maybe a3530822107858468865) (Symbol ~> Symbol) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings (FromMaybeSym1 a6989586621679494793 :: TyFun (Maybe a6989586621679494601) a6989586621679494601 -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (TFHelper_6989586621679607586Sym1 a6989586621679607584 :: TyFun (Maybe a6989586621679544211) (Maybe a6989586621679544211) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (TFHelper_6989586621679607486Sym0 :: TyFun (Maybe a6989586621679544159) (Maybe b6989586621679544160 ~> Maybe b6989586621679544160) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (TFHelper_6989586621679607470Sym0 :: TyFun (Maybe a6989586621679544157) ((a6989586621679544157 ~> Maybe b6989586621679544158) ~> Maybe b6989586621679544158) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (TFHelper_6989586621679607328Sym0 :: TyFun (Maybe a6989586621679544139) (Maybe b6989586621679544140 ~> Maybe b6989586621679544140) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (Compare_6989586621679390320Sym1 a6989586621679390318 :: TyFun (Maybe a3530822107858468865) Ordering -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (TFHelper_6989586621679607298Sym0 :: TyFun (Maybe (a6989586621679544134 ~> b6989586621679544135)) (Maybe a6989586621679544134 ~> Maybe b6989586621679544135) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (Maybe_Sym0 :: TyFun b6989586621679493174 ((a6989586621679493175 ~> b6989586621679493174) ~> (Maybe a6989586621679493175 ~> b6989586621679493174)) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (LookupSym0 :: TyFun a6989586621679939137 ([(a6989586621679939137, b6989586621679939138)] ~> Maybe b6989586621679939138) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (TFHelper_6989586621679607157Sym0 :: TyFun a6989586621679544130 (Maybe b6989586621679544131 ~> Maybe a6989586621679544130) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (Let6989586621680442002NSym0 :: TyFun k (TyFun k1 (Maybe k1) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680442002MSym0 :: TyFun k1 (TyFun k (Maybe k1) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680441975NSym0 :: TyFun k (TyFun k1 (Maybe k1) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680441975MSym0 :: TyFun k1 (TyFun k (Maybe k1) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (MapMaybeSym0 :: TyFun (a6989586621679494596 ~> Maybe b6989586621679494597) ([a6989586621679494596] ~> [b6989586621679494597]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (UnfoldrSym0 :: TyFun (b6989586621679939215 ~> Maybe (a6989586621679939216, b6989586621679939215)) (b6989586621679939215 ~> [a6989586621679939216]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Fmap_6989586621679607137Sym0 :: TyFun (a6989586621679544128 ~> b6989586621679544129) (Maybe a6989586621679544128 ~> Maybe b6989586621679544129) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (FindSym0 :: TyFun (a6989586621680450093 ~> Bool) (t6989586621680450092 a6989586621680450093 ~> Maybe a6989586621680450093) -> 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 a6989586621679948498 b6989586621679939138 :: TyFun [(a6989586621679939137, b6989586621679939138)] (Maybe b6989586621679939138) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (TFHelper_6989586621679607486Sym1 a6989586621679607484 b6989586621679544160 :: TyFun (Maybe b6989586621679544160) (Maybe b6989586621679544160) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (TFHelper_6989586621679607328Sym1 a6989586621679607326 b6989586621679544140 :: TyFun (Maybe b6989586621679544140) (Maybe b6989586621679544140) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (TFHelper_6989586621679607298Sym1 a6989586621679607296 :: TyFun (Maybe a6989586621679544134) (Maybe b6989586621679544135) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (TFHelper_6989586621679607157Sym1 a6989586621679607155 b6989586621679544131 :: TyFun (Maybe b6989586621679544131) (Maybe a6989586621679544130) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (Fmap_6989586621679607137Sym1 a6989586621679607135 :: TyFun (Maybe a6989586621679544128) (Maybe b6989586621679544129) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (Let6989586621680442002NSym1 x6989586621680442000 :: TyFun k1 (Maybe k1) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680442002MSym1 x6989586621680442000 :: TyFun k (Maybe k1) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680441975NSym1 x6989586621680441973 :: TyFun k1 (Maybe k1) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680441975MSym1 x6989586621680441973 :: TyFun k (Maybe k1) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (FindSym1 a6989586621680450550 t6989586621680450092 :: TyFun (t6989586621680450092 a6989586621680450093) (Maybe a6989586621680450093) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Lambda_6989586621680338356Sym0 :: TyFun k (TyFun (k1 ~> Last a) (TyFun k1 (Maybe a) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

SuppressUnusedWarnings (Lambda_6989586621680338268Sym0 :: TyFun k (TyFun (k1 ~> First a) (TyFun k1 (Maybe a) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

SuppressUnusedWarnings (Traverse_6989586621680753858Sym0 :: TyFun (a6989586621680747697 ~> f6989586621680747696 b6989586621680747698) (Maybe a6989586621680747697 ~> f6989586621680747696 (Maybe b6989586621680747698)) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Traversable

SuppressUnusedWarnings (Maybe_Sym1 a6989586621679493192 a6989586621679493175 :: TyFun (a6989586621679493175 ~> b6989586621679493174) (Maybe a6989586621679493175 ~> b6989586621679493174) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (Let6989586621679494770RsSym0 :: TyFun (a6989586621679494596 ~> Maybe k1) (TyFun k (TyFun [a6989586621679494596] [k1] -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (TFHelper_6989586621679607470Sym1 a6989586621679607468 b6989586621679544158 :: TyFun (a6989586621679544157 ~> Maybe b6989586621679544158) (Maybe b6989586621679544158) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (LiftA2_6989586621679607314Sym0 :: TyFun (a6989586621679544136 ~> (b6989586621679544137 ~> c6989586621679544138)) (Maybe a6989586621679544136 ~> (Maybe b6989586621679544137 ~> Maybe c6989586621679544138)) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (Let6989586621680451027MfSym0 :: 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 (Let6989586621680451002MfSym0 :: 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_6989586621680753858Sym1 a6989586621680753856 :: TyFun (Maybe a6989586621680747697) (f6989586621680747696 (Maybe b6989586621680747698)) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Traversable

SuppressUnusedWarnings (Maybe_Sym2 a6989586621679493193 a6989586621679493192 :: TyFun (Maybe a6989586621679493175) b6989586621679493174 -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (LiftA2_6989586621679607314Sym1 a6989586621679607311 :: TyFun (Maybe a6989586621679544136) (Maybe b6989586621679544137 ~> Maybe c6989586621679544138) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (Let6989586621680451027MfSym1 f6989586621680451025 :: TyFun k (TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680451002MfSym1 f6989586621680451000 :: TyFun k (TyFun k3 (TyFun (Maybe k2) (Maybe k3) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Lambda_6989586621680338356Sym1 a6989586621680338354 :: TyFun (k1 ~> Last a) (TyFun k1 (Maybe a) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

SuppressUnusedWarnings (Lambda_6989586621680338268Sym1 a6989586621680338266 :: 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_6989586621679607314Sym2 a6989586621679607312 a6989586621679607311 :: TyFun (Maybe b6989586621679544137) (Maybe c6989586621679544138) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (Let6989586621680451027MfSym2 xs6989586621680451026 f6989586621680451025 :: TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680451002MfSym2 xs6989586621680451001 f6989586621680451000 :: TyFun k3 (TyFun (Maybe k2) (Maybe k3) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Lambda_6989586621680338356Sym2 k6989586621680338355 a6989586621680338354 :: TyFun k1 (Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

SuppressUnusedWarnings (Lambda_6989586621680338268Sym2 k6989586621680338267 a6989586621680338266 :: TyFun k1 (Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

SuppressUnusedWarnings (Let6989586621680451002MfSym3 a6989586621680451003 xs6989586621680451001 f6989586621680451000 :: TyFun (Maybe k2) (Maybe k3) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680451027MfSym3 a6989586621680451028 xs6989586621680451026 f6989586621680451025 :: TyFun k3 (Maybe k3) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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_6989586621679607574Sym0 :: Maybe a)
type Mzero 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Mzero = (Mzero_6989586621679544686Sym0 :: Maybe a)
type Product (arg :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Product (arg :: Maybe a) = Apply (Product_6989586621680451163Sym0 :: 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_6989586621680451150Sym0 :: 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_6989586621680451137Sym0 :: 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_6989586621680451124Sym0 :: 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_6989586621680451095Sym0 :: 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_6989586621680451073Sym0 :: 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_6989586621680451052Sym0 :: 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_6989586621680450869Sym0 :: 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_6989586621679607286Sym0 :: TyFun k1 (Maybe k1) -> Type) a
type Fail a2 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Fail a2 = Apply (Fail_6989586621679607493Sym0 :: 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_6989586621679544668Sym0 :: 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_6989586621680747764Sym0 :: 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_6989586621680747739Sym0 :: 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_6989586621680451110Sym0 :: 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_6989586621680451042Sym0 :: 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_6989586621680451017Sym0 :: TyFun (a ~> (a ~> a)) (Maybe a ~> a) -> Type) arg1) arg2
type (a1 :: Maybe a6989586621679544211) <|> (a2 :: Maybe a6989586621679544211) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type (a1 :: Maybe a6989586621679544211) <|> (a2 :: Maybe a6989586621679544211) = Apply (Apply (TFHelper_6989586621679607586Sym0 :: TyFun (Maybe a6989586621679544211) (Maybe a6989586621679544211 ~> Maybe a6989586621679544211) -> 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_6989586621679544700Sym0 :: TyFun (Maybe a) (Maybe a ~> Maybe a) -> Type) arg1) arg2
type FoldMap (a1 :: a6989586621680450187 ~> k2) (a2 :: Maybe a6989586621680450187) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type FoldMap (a1 :: a6989586621680450187 ~> k2) (a2 :: Maybe a6989586621680450187) = Apply (Apply (FoldMap_6989586621680451181Sym0 :: TyFun (a6989586621680450187 ~> k2) (Maybe a6989586621680450187 ~> k2) -> Type) a1) a2
type (a1 :: k1) <$ (a2 :: Maybe b6989586621679544131) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type (a1 :: k1) <$ (a2 :: Maybe b6989586621679544131) = Apply (Apply (TFHelper_6989586621679607157Sym0 :: TyFun k1 (Maybe b6989586621679544131 ~> Maybe k1) -> Type) a1) a2
type Fmap (a1 :: a6989586621679544128 ~> b6989586621679544129) (a2 :: Maybe a6989586621679544128) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Fmap (a1 :: a6989586621679544128 ~> b6989586621679544129) (a2 :: Maybe a6989586621679544128) = Apply (Apply (Fmap_6989586621679607137Sym0 :: TyFun (a6989586621679544128 ~> b6989586621679544129) (Maybe a6989586621679544128 ~> Maybe b6989586621679544129) -> 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_6989586621679544624Sym0 :: TyFun (Maybe a) (Maybe b ~> Maybe a) -> Type) arg1) arg2
type (a1 :: Maybe a6989586621679544139) *> (a2 :: Maybe b6989586621679544140) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type (a1 :: Maybe a6989586621679544139) *> (a2 :: Maybe b6989586621679544140) = Apply (Apply (TFHelper_6989586621679607328Sym0 :: TyFun (Maybe a6989586621679544139) (Maybe b6989586621679544140 ~> Maybe b6989586621679544140) -> Type) a1) a2
type (a1 :: Maybe (a6989586621679544134 ~> b6989586621679544135)) <*> (a2 :: Maybe a6989586621679544134) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type (a1 :: Maybe (a6989586621679544134 ~> b6989586621679544135)) <*> (a2 :: Maybe a6989586621679544134) = Apply (Apply (TFHelper_6989586621679607298Sym0 :: TyFun (Maybe (a6989586621679544134 ~> b6989586621679544135)) (Maybe a6989586621679544134 ~> Maybe b6989586621679544135) -> Type) a1) a2
type (a1 :: Maybe a6989586621679544159) >> (a2 :: Maybe b6989586621679544160) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type (a1 :: Maybe a6989586621679544159) >> (a2 :: Maybe b6989586621679544160) = Apply (Apply (TFHelper_6989586621679607486Sym0 :: TyFun (Maybe a6989586621679544159) (Maybe b6989586621679544160 ~> Maybe b6989586621679544160) -> Type) a1) a2
type (a1 :: Maybe a6989586621679544157) >>= (a2 :: a6989586621679544157 ~> Maybe b6989586621679544158) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type (a1 :: Maybe a6989586621679544157) >>= (a2 :: a6989586621679544157 ~> Maybe b6989586621679544158) = Apply (Apply (TFHelper_6989586621679607470Sym0 :: TyFun (Maybe a6989586621679544157) ((a6989586621679544157 ~> Maybe b6989586621679544158) ~> Maybe b6989586621679544158) -> 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_6989586621680747754Sym0 :: TyFun (a ~> m b) (Maybe a ~> m (Maybe b)) -> Type) arg1) arg2
type Traverse (a1 :: a6989586621680747697 ~> f6989586621680747696 b6989586621680747698) (a2 :: Maybe a6989586621680747697) 
Instance details

Defined in Data.Singletons.Prelude.Traversable

type Traverse (a1 :: a6989586621680747697 ~> f6989586621680747696 b6989586621680747698) (a2 :: Maybe a6989586621680747697) = Apply (Apply (Traverse_6989586621680753858Sym0 :: TyFun (a6989586621680747697 ~> f6989586621680747696 b6989586621680747698) (Maybe a6989586621680747697 ~> f6989586621680747696 (Maybe b6989586621680747698)) -> 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'_6989586621680450991Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (Maybe a ~> b)) -> Type) arg1) arg2) arg3
type Foldl (a1 :: k2 ~> (a6989586621680450193 ~> k2)) (a2 :: k2) (a3 :: Maybe a6989586621680450193) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl (a1 :: k2 ~> (a6989586621680450193 ~> k2)) (a2 :: k2) (a3 :: Maybe a6989586621680450193) = Apply (Apply (Apply (Foldl_6989586621680451216Sym0 :: TyFun (k2 ~> (a6989586621680450193 ~> k2)) (k2 ~> (Maybe a6989586621680450193 ~> 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'_6989586621680450936Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (Maybe a ~> b)) -> Type) arg1) arg2) arg3
type Foldr (a1 :: a6989586621680450188 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Maybe a6989586621680450188) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldr (a1 :: a6989586621680450188 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Maybe a6989586621680450188) = Apply (Apply (Apply (Foldr_6989586621680451198Sym0 :: TyFun (a6989586621680450188 ~> (k2 ~> k2)) (k2 ~> (Maybe a6989586621680450188 ~> k2)) -> Type) a1) a2) a3
type LiftA2 (a1 :: a6989586621679544136 ~> (b6989586621679544137 ~> c6989586621679544138)) (a2 :: Maybe a6989586621679544136) (a3 :: Maybe b6989586621679544137) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type LiftA2 (a1 :: a6989586621679544136 ~> (b6989586621679544137 ~> c6989586621679544138)) (a2 :: Maybe a6989586621679544136) (a3 :: Maybe b6989586621679544137) = Apply (Apply (Apply (LiftA2_6989586621679607314Sym0 :: TyFun (a6989586621679544136 ~> (b6989586621679544137 ~> c6989586621679544138)) (Maybe a6989586621679544136 ~> (Maybe b6989586621679544137 ~> Maybe c6989586621679544138)) -> Type) a1) a2) a3
type Apply (IsNothingSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679494806 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

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

Defined in Data.Singletons.Prelude.Maybe

type Apply (IsJustSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679494808 :: Maybe a) = IsJust a6989586621679494808
type Apply (FromJustSym0 :: TyFun (Maybe a) a -> Type) (a6989586621679494803 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (FromJustSym0 :: TyFun (Maybe a) a -> Type) (a6989586621679494803 :: Maybe a) = FromJust a6989586621679494803
type Apply (Compare_6989586621679390320Sym1 a6989586621679390318 :: TyFun (Maybe a) Ordering -> Type) (a6989586621679390319 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Compare_6989586621679390320Sym1 a6989586621679390318 :: TyFun (Maybe a) Ordering -> Type) (a6989586621679390319 :: Maybe a) = Compare_6989586621679390320 a6989586621679390318 a6989586621679390319
type Apply (FromMaybeSym1 a6989586621679494793 :: TyFun (Maybe a) a -> Type) (a6989586621679494794 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (FromMaybeSym1 a6989586621679494793 :: TyFun (Maybe a) a -> Type) (a6989586621679494794 :: Maybe a) = FromMaybe a6989586621679494793 a6989586621679494794
type Apply (Maybe_Sym2 a6989586621679493193 a6989586621679493192 :: TyFun (Maybe a) b -> Type) (a6989586621679493194 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (Maybe_Sym2 a6989586621679493193 a6989586621679493192 :: TyFun (Maybe a) b -> Type) (a6989586621679493194 :: Maybe a) = Maybe_ a6989586621679493193 a6989586621679493192 a6989586621679493194
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_6989586621680328725Sym0 :: 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_6989586621680328675Sym0 :: 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__6989586621680262174Sym0 :: 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_6989586621679810446Sym0 :: 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_6989586621680328665Sym0 :: 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_6989586621680262185Sym0 :: 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_6989586621679810618Sym0 :: 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_6989586621679379679Sym0 :: 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_6989586621679379661Sym0 :: 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_6989586621679379643Sym0 :: 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_6989586621679379625Sym0 :: 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_6989586621679379607Sym0 :: 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_6989586621679379589Sym0 :: 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_6989586621679390320Sym0 :: 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_6989586621679364159 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_6989586621680280310Sym0 :: TyFun Nat (Maybe a1 ~> (Symbol ~> Symbol)) -> Type) a2) a3) a4
type Apply (Pure_6989586621679607286Sym0 :: TyFun a (Maybe a) -> Type) (a6989586621679607285 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (Pure_6989586621679607286Sym0 :: TyFun a (Maybe a) -> Type) (a6989586621679607285 :: a) = Pure_6989586621679607286 a6989586621679607285
type Apply (Fail_6989586621679607493Sym0 :: TyFun Symbol (Maybe a6989586621679544162) -> Type) (a6989586621679607492 :: Symbol) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (Fail_6989586621679607493Sym0 :: TyFun Symbol (Maybe a6989586621679544162) -> Type) (a6989586621679607492 :: Symbol) = (Fail_6989586621679607493 a6989586621679607492 :: Maybe a6989586621679544162)
type Apply (Let6989586621679607582LSym0 :: TyFun k1 (Maybe k1) -> Type) (wild_69895866216796067436989586621679607581 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (Let6989586621679607582LSym0 :: TyFun k1 (Maybe k1) -> Type) (wild_69895866216796067436989586621679607581 :: k1) = Let6989586621679607582L wild_69895866216796067436989586621679607581
type Apply (JustSym0 :: TyFun a (Maybe a) -> Type) (t6989586621679294037 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Apply (JustSym0 :: TyFun a (Maybe a) -> Type) (t6989586621679294037 :: a) = Just t6989586621679294037
type Apply (Let6989586621680441975MSym1 x6989586621680441973 :: TyFun k (Maybe k1) -> Type) (y6989586621680441974 :: k) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680441975MSym1 x6989586621680441973 :: TyFun k (Maybe k1) -> Type) (y6989586621680441974 :: k) = Let6989586621680441975M x6989586621680441973 y6989586621680441974
type Apply (Let6989586621680441975NSym1 x6989586621680441973 :: TyFun k1 (Maybe k1) -> Type) (y6989586621680441974 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680441975NSym1 x6989586621680441973 :: TyFun k1 (Maybe k1) -> Type) (y6989586621680441974 :: k1) = Let6989586621680441975N x6989586621680441973 y6989586621680441974
type Apply (Let6989586621680442002MSym1 x6989586621680442000 :: TyFun k (Maybe k1) -> Type) (y6989586621680442001 :: k) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680442002MSym1 x6989586621680442000 :: TyFun k (Maybe k1) -> Type) (y6989586621680442001 :: k) = Let6989586621680442002M x6989586621680442000 y6989586621680442001
type Apply (Let6989586621680442002NSym1 x6989586621680442000 :: TyFun k1 (Maybe k1) -> Type) (y6989586621680442001 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680442002NSym1 x6989586621680442000 :: TyFun k1 (Maybe k1) -> Type) (y6989586621680442001 :: k1) = Let6989586621680442002N x6989586621680442000 y6989586621680442001
type Apply (Lambda_6989586621680338268Sym2 k6989586621680338267 a6989586621680338266 :: TyFun k1 (Maybe a) -> Type) (t6989586621680338279 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (Lambda_6989586621680338268Sym2 k6989586621680338267 a6989586621680338266 :: TyFun k1 (Maybe a) -> Type) (t6989586621680338279 :: k1) = Lambda_6989586621680338268 k6989586621680338267 a6989586621680338266 t6989586621680338279
type Apply (Lambda_6989586621680338356Sym2 k6989586621680338355 a6989586621680338354 :: TyFun k1 (Maybe a) -> Type) (t6989586621680338367 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (Lambda_6989586621680338356Sym2 k6989586621680338355 a6989586621680338354 :: TyFun k1 (Maybe a) -> Type) (t6989586621680338367 :: k1) = Lambda_6989586621680338356 k6989586621680338355 a6989586621680338354 t6989586621680338367
type Apply (Let6989586621680451027MfSym3 a6989586621680451028 xs6989586621680451026 f6989586621680451025 :: TyFun k3 (Maybe k3) -> Type) (a6989586621680451029 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680451027MfSym3 a6989586621680451028 xs6989586621680451026 f6989586621680451025 :: TyFun k3 (Maybe k3) -> Type) (a6989586621680451029 :: k3) = Let6989586621680451027Mf a6989586621680451028 xs6989586621680451026 f6989586621680451025 a6989586621680451029
type Apply (CatMaybesSym0 :: TyFun [Maybe a] [a] -> Type) (a6989586621679494782 :: [Maybe a]) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (CatMaybesSym0 :: TyFun [Maybe a] [a] -> Type) (a6989586621679494782 :: [Maybe a]) = CatMaybes a6989586621679494782
type Apply (MaybeToListSym0 :: TyFun (Maybe a) [a] -> Type) (a6989586621679494790 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (MaybeToListSym0 :: TyFun (Maybe a) [a] -> Type) (a6989586621679494790 :: Maybe a) = MaybeToList a6989586621679494790
type Apply (ListToMaybeSym0 :: TyFun [a] (Maybe a) -> Type) (a6989586621679494787 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (ListToMaybeSym0 :: TyFun [a] (Maybe a) -> Type) (a6989586621679494787 :: [a]) = ListToMaybe a6989586621679494787
type Apply (GetOptionSym0 :: TyFun (Option a) (Maybe a) -> Type) (a6989586621679819627 :: Option a) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply (GetOptionSym0 :: TyFun (Option a) (Maybe a) -> Type) (a6989586621679819627 :: Option a) = GetOption a6989586621679819627
type Apply (GetFirstSym0 :: TyFun (First a) (Maybe a) -> Type) (a6989586621680332173 :: First a) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (GetFirstSym0 :: TyFun (First a) (Maybe a) -> Type) (a6989586621680332173 :: First a) = GetFirst a6989586621680332173
type Apply (GetLastSym0 :: TyFun (Last a) (Maybe a) -> Type) (a6989586621680332194 :: Last a) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (GetLastSym0 :: TyFun (Last a) (Maybe a) -> Type) (a6989586621680332194 :: Last a) = GetLast a6989586621680332194
type Apply (OptionSym0 :: TyFun (Maybe a) (Option a) -> Type) (t6989586621679819630 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply (OptionSym0 :: TyFun (Maybe a) (Option a) -> Type) (t6989586621679819630 :: Maybe a) = Option t6989586621679819630
type Apply (FirstSym0 :: TyFun (Maybe a) (First a) -> Type) (t6989586621680332176 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (FirstSym0 :: TyFun (Maybe a) (First a) -> Type) (t6989586621680332176 :: Maybe a) = First t6989586621680332176
type Apply (LastSym0 :: TyFun (Maybe a) (Last a) -> Type) (t6989586621680332197 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (LastSym0 :: TyFun (Maybe a) (Last a) -> Type) (t6989586621680332197 :: Maybe a) = Last t6989586621680332197
type Apply (MaxInternalSym0 :: TyFun (Maybe a) (MaxInternal a) -> Type) (t6989586621680441196 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MaxInternalSym0 :: TyFun (Maybe a) (MaxInternal a) -> Type) (t6989586621680441196 :: Maybe a) = MaxInternal t6989586621680441196
type Apply (MinInternalSym0 :: TyFun (Maybe a) (MinInternal a) -> Type) (t6989586621680441396 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MinInternalSym0 :: TyFun (Maybe a) (MinInternal a) -> Type) (t6989586621680441396 :: Maybe a) = MinInternal t6989586621680441396
type Apply (StripPrefixSym1 a6989586621680078084 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621680078085 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (StripPrefixSym1 a6989586621680078084 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621680078085 :: [a]) = StripPrefix a6989586621680078084 a6989586621680078085
type Apply (FindIndexSym1 a6989586621679949076 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679949077 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FindIndexSym1 a6989586621679949076 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679949077 :: [a]) = FindIndex a6989586621679949076 a6989586621679949077
type Apply (ElemIndexSym1 a6989586621679949084 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679949085 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ElemIndexSym1 a6989586621679949084 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679949085 :: [a]) = ElemIndex a6989586621679949084 a6989586621679949085
type Apply (FindSym1 a6989586621679948716 :: TyFun [a] (Maybe a) -> Type) (a6989586621679948717 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FindSym1 a6989586621679948716 :: TyFun [a] (Maybe a) -> Type) (a6989586621679948717 :: [a]) = Find a6989586621679948716 a6989586621679948717
type Apply (TFHelper_6989586621679607586Sym1 a6989586621679607584 :: TyFun (Maybe a) (Maybe a) -> Type) (a6989586621679607585 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621679607586Sym1 a6989586621679607584 :: TyFun (Maybe a) (Maybe a) -> Type) (a6989586621679607585 :: Maybe a) = TFHelper_6989586621679607586 a6989586621679607584 a6989586621679607585
type Apply (LookupSym1 a6989586621679948498 b :: TyFun [(a, b)] (Maybe b) -> Type) (a6989586621679948499 :: [(a, b)]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (LookupSym1 a6989586621679948498 b :: TyFun [(a, b)] (Maybe b) -> Type) (a6989586621679948499 :: [(a, b)]) = Lookup a6989586621679948498 a6989586621679948499
type Apply (Fmap_6989586621679607137Sym1 a6989586621679607135 :: TyFun (Maybe a) (Maybe b) -> Type) (a6989586621679607136 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (Fmap_6989586621679607137Sym1 a6989586621679607135 :: TyFun (Maybe a) (Maybe b) -> Type) (a6989586621679607136 :: Maybe a) = Fmap_6989586621679607137 a6989586621679607135 a6989586621679607136
type Apply (TFHelper_6989586621679607157Sym1 a6989586621679607155 b :: TyFun (Maybe b) (Maybe a) -> Type) (a6989586621679607156 :: Maybe b) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621679607157Sym1 a6989586621679607155 b :: TyFun (Maybe b) (Maybe a) -> Type) (a6989586621679607156 :: Maybe b) = TFHelper_6989586621679607157 a6989586621679607155 a6989586621679607156
type Apply (TFHelper_6989586621679607298Sym1 a6989586621679607296 :: TyFun (Maybe a) (Maybe b) -> Type) (a6989586621679607297 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621679607298Sym1 a6989586621679607296 :: TyFun (Maybe a) (Maybe b) -> Type) (a6989586621679607297 :: Maybe a) = TFHelper_6989586621679607298 a6989586621679607296 a6989586621679607297
type Apply (TFHelper_6989586621679607328Sym1 a6989586621679607326 b :: TyFun (Maybe b) (Maybe b) -> Type) (a6989586621679607327 :: Maybe b) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621679607328Sym1 a6989586621679607326 b :: TyFun (Maybe b) (Maybe b) -> Type) (a6989586621679607327 :: Maybe b) = TFHelper_6989586621679607328 a6989586621679607326 a6989586621679607327
type Apply (TFHelper_6989586621679607486Sym1 a6989586621679607484 b :: TyFun (Maybe b) (Maybe b) -> Type) (a6989586621679607485 :: Maybe b) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621679607486Sym1 a6989586621679607484 b :: TyFun (Maybe b) (Maybe b) -> Type) (a6989586621679607485 :: Maybe b) = TFHelper_6989586621679607486 a6989586621679607484 a6989586621679607485
type Apply (FindSym1 a6989586621680450550 t :: TyFun (t a) (Maybe a) -> Type) (a6989586621680450551 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FindSym1 a6989586621680450550 t :: TyFun (t a) (Maybe a) -> Type) (a6989586621680450551 :: t a) = Find a6989586621680450550 a6989586621680450551
type Apply (Traverse_6989586621680753858Sym1 a6989586621680753856 :: TyFun (Maybe a) (f (Maybe b)) -> Type) (a6989586621680753857 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Traversable

type Apply (Traverse_6989586621680753858Sym1 a6989586621680753856 :: TyFun (Maybe a) (f (Maybe b)) -> Type) (a6989586621680753857 :: Maybe a) = Traverse_6989586621680753858 a6989586621680753856 a6989586621680753857
type Apply (LiftA2_6989586621679607314Sym2 a6989586621679607312 a6989586621679607311 :: TyFun (Maybe b) (Maybe c) -> Type) (a6989586621679607313 :: Maybe b) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (LiftA2_6989586621679607314Sym2 a6989586621679607312 a6989586621679607311 :: TyFun (Maybe b) (Maybe c) -> Type) (a6989586621679607313 :: Maybe b) = LiftA2_6989586621679607314 a6989586621679607312 a6989586621679607311 a6989586621679607313
type Apply (Let6989586621680451002MfSym3 a6989586621680451003 xs6989586621680451001 f6989586621680451000 :: TyFun (Maybe k2) (Maybe k3) -> Type) (a6989586621680451004 :: Maybe k2) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680451002MfSym3 a6989586621680451003 xs6989586621680451001 f6989586621680451000 :: TyFun (Maybe k2) (Maybe k3) -> Type) (a6989586621680451004 :: Maybe k2) = Let6989586621680451002Mf a6989586621680451003 xs6989586621680451001 f6989586621680451000 a6989586621680451004
type Apply (TFHelper_6989586621679607470Sym1 a6989586621679607468 b :: TyFun (a ~> Maybe b) (Maybe b) -> Type) (a6989586621679607469 :: a ~> Maybe b) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621679607470Sym1 a6989586621679607468 b :: TyFun (a ~> Maybe b) (Maybe b) -> Type) (a6989586621679607469 :: a ~> Maybe b) = TFHelper_6989586621679607470 a6989586621679607468 a6989586621679607469
type Apply (ElemIndexSym0 :: TyFun a6989586621679939158 ([a6989586621679939158] ~> Maybe Nat) -> Type) (a6989586621679949084 :: a6989586621679939158) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ElemIndexSym0 :: TyFun a6989586621679939158 ([a6989586621679939158] ~> Maybe Nat) -> Type) (a6989586621679949084 :: a6989586621679939158) = ElemIndexSym1 a6989586621679949084
type Apply (ShowsPrec_6989586621680280310Sym0 :: TyFun Nat (Maybe a3530822107858468865 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680280307 :: Nat) 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowsPrec_6989586621680280310Sym0 :: TyFun Nat (Maybe a3530822107858468865 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680280307 :: Nat) = (ShowsPrec_6989586621680280310Sym1 a6989586621680280307 a3530822107858468865 :: TyFun (Maybe a3530822107858468865) (Symbol ~> Symbol) -> Type)
type Apply (FromMaybeSym0 :: TyFun a6989586621679494601 (Maybe a6989586621679494601 ~> a6989586621679494601) -> Type) (a6989586621679494793 :: a6989586621679494601) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (FromMaybeSym0 :: TyFun a6989586621679494601 (Maybe a6989586621679494601 ~> a6989586621679494601) -> Type) (a6989586621679494793 :: a6989586621679494601) = FromMaybeSym1 a6989586621679494793
type Apply (Let6989586621680441975MSym0 :: TyFun k1 (TyFun k (Maybe k1) -> Type) -> Type) (x6989586621680441973 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680441975MSym0 :: TyFun k1 (TyFun k (Maybe k1) -> Type) -> Type) (x6989586621680441973 :: k1) = (Let6989586621680441975MSym1 x6989586621680441973 :: TyFun k (Maybe k1) -> Type)
type Apply (Let6989586621680441975NSym0 :: TyFun k (TyFun k1 (Maybe k1) -> Type) -> Type) (x6989586621680441973 :: k) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680441975NSym0 :: TyFun k (TyFun k1 (Maybe k1) -> Type) -> Type) (x6989586621680441973 :: k) = (Let6989586621680441975NSym1 x6989586621680441973 :: TyFun k1 (Maybe k1) -> Type)
type Apply (Let6989586621680442002MSym0 :: TyFun k1 (TyFun k (Maybe k1) -> Type) -> Type) (x6989586621680442000 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680442002MSym0 :: TyFun k1 (TyFun k (Maybe k1) -> Type) -> Type) (x6989586621680442000 :: k1) = (Let6989586621680442002MSym1 x6989586621680442000 :: TyFun k (Maybe k1) -> Type)
type Apply (Let6989586621680442002NSym0 :: TyFun k (TyFun k1 (Maybe k1) -> Type) -> Type) (x6989586621680442000 :: k) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680442002NSym0 :: TyFun k (TyFun k1 (Maybe k1) -> Type) -> Type) (x6989586621680442000 :: k) = (Let6989586621680442002NSym1 x6989586621680442000 :: TyFun k1 (Maybe k1) -> Type)
type Apply (LookupSym0 :: TyFun a6989586621679939137 ([(a6989586621679939137, b6989586621679939138)] ~> Maybe b6989586621679939138) -> Type) (a6989586621679948498 :: a6989586621679939137) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (LookupSym0 :: TyFun a6989586621679939137 ([(a6989586621679939137, b6989586621679939138)] ~> Maybe b6989586621679939138) -> Type) (a6989586621679948498 :: a6989586621679939137) = (LookupSym1 a6989586621679948498 b6989586621679939138 :: TyFun [(a6989586621679939137, b6989586621679939138)] (Maybe b6989586621679939138) -> Type)
type Apply (TFHelper_6989586621679607157Sym0 :: TyFun a6989586621679544130 (Maybe b6989586621679544131 ~> Maybe a6989586621679544130) -> Type) (a6989586621679607155 :: a6989586621679544130) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621679607157Sym0 :: TyFun a6989586621679544130 (Maybe b6989586621679544131 ~> Maybe a6989586621679544130) -> Type) (a6989586621679607155 :: a6989586621679544130) = (TFHelper_6989586621679607157Sym1 a6989586621679607155 b6989586621679544131 :: TyFun (Maybe b6989586621679544131) (Maybe a6989586621679544130) -> Type)
type Apply (Maybe_Sym0 :: TyFun b6989586621679493174 ((a6989586621679493175 ~> b6989586621679493174) ~> (Maybe a6989586621679493175 ~> b6989586621679493174)) -> Type) (a6989586621679493192 :: b6989586621679493174) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (Maybe_Sym0 :: TyFun b6989586621679493174 ((a6989586621679493175 ~> b6989586621679493174) ~> (Maybe a6989586621679493175 ~> b6989586621679493174)) -> Type) (a6989586621679493192 :: b6989586621679493174) = (Maybe_Sym1 a6989586621679493192 a6989586621679493175 :: TyFun (a6989586621679493175 ~> b6989586621679493174) (Maybe a6989586621679493175 ~> b6989586621679493174) -> Type)
type Apply (Lambda_6989586621680338268Sym0 :: TyFun k (TyFun (k1 ~> First a) (TyFun k1 (Maybe a) -> Type) -> Type) -> Type) (a6989586621680338266 :: k) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (Lambda_6989586621680338268Sym0 :: TyFun k (TyFun (k1 ~> First a) (TyFun k1 (Maybe a) -> Type) -> Type) -> Type) (a6989586621680338266 :: k) = (Lambda_6989586621680338268Sym1 a6989586621680338266 :: TyFun (k1 ~> First a) (TyFun k1 (Maybe a) -> Type) -> Type)
type Apply (Lambda_6989586621680338356Sym0 :: TyFun k (TyFun (k1 ~> Last a) (TyFun k1 (Maybe a) -> Type) -> Type) -> Type) (a6989586621680338354 :: k) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (Lambda_6989586621680338356Sym0 :: TyFun k (TyFun (k1 ~> Last a) (TyFun k1 (Maybe a) -> Type) -> Type) -> Type) (a6989586621680338354 :: k) = (Lambda_6989586621680338356Sym1 a6989586621680338354 :: TyFun (k1 ~> Last a) (TyFun k1 (Maybe a) -> Type) -> Type)
type Apply (Let6989586621680451027MfSym1 f6989586621680451025 :: TyFun k (TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) -> Type) (xs6989586621680451026 :: k) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680451027MfSym1 f6989586621680451025 :: TyFun k (TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) -> Type) (xs6989586621680451026 :: k) = Let6989586621680451027MfSym2 f6989586621680451025 xs6989586621680451026
type Apply (Let6989586621680451002MfSym1 f6989586621680451000 :: TyFun k (TyFun k3 (TyFun (Maybe k2) (Maybe k3) -> Type) -> Type) -> Type) (xs6989586621680451001 :: k) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680451002MfSym1 f6989586621680451000 :: TyFun k (TyFun k3 (TyFun (Maybe k2) (Maybe k3) -> Type) -> Type) -> Type) (xs6989586621680451001 :: k) = Let6989586621680451002MfSym2 f6989586621680451000 xs6989586621680451001
type Apply (Let6989586621680451002MfSym2 xs6989586621680451001 f6989586621680451000 :: TyFun k3 (TyFun (Maybe k2) (Maybe k3) -> Type) -> Type) (a6989586621680451003 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680451002MfSym2 xs6989586621680451001 f6989586621680451000 :: TyFun k3 (TyFun (Maybe k2) (Maybe k3) -> Type) -> Type) (a6989586621680451003 :: k3) = Let6989586621680451002MfSym3 xs6989586621680451001 f6989586621680451000 a6989586621680451003
type Apply (StripPrefixSym0 :: TyFun [a6989586621680065374] ([a6989586621680065374] ~> Maybe [a6989586621680065374]) -> Type) (a6989586621680078084 :: [a6989586621680065374]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (StripPrefixSym0 :: TyFun [a6989586621680065374] ([a6989586621680065374] ~> Maybe [a6989586621680065374]) -> Type) (a6989586621680078084 :: [a6989586621680065374]) = StripPrefixSym1 a6989586621680078084
type Apply (TFHelper_6989586621679607586Sym0 :: TyFun (Maybe a6989586621679544211) (Maybe a6989586621679544211 ~> Maybe a6989586621679544211) -> Type) (a6989586621679607584 :: Maybe a6989586621679544211) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621679607586Sym0 :: TyFun (Maybe a6989586621679544211) (Maybe a6989586621679544211 ~> Maybe a6989586621679544211) -> Type) (a6989586621679607584 :: Maybe a6989586621679544211) = TFHelper_6989586621679607586Sym1 a6989586621679607584
type Apply (Compare_6989586621679390320Sym0 :: TyFun (Maybe a3530822107858468865) (Maybe a3530822107858468865 ~> Ordering) -> Type) (a6989586621679390318 :: Maybe a3530822107858468865) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Compare_6989586621679390320Sym0 :: TyFun (Maybe a3530822107858468865) (Maybe a3530822107858468865 ~> Ordering) -> Type) (a6989586621679390318 :: Maybe a3530822107858468865) = Compare_6989586621679390320Sym1 a6989586621679390318
type Apply (TFHelper_6989586621679607298Sym0 :: TyFun (Maybe (a6989586621679544134 ~> b6989586621679544135)) (Maybe a6989586621679544134 ~> Maybe b6989586621679544135) -> Type) (a6989586621679607296 :: Maybe (a6989586621679544134 ~> b6989586621679544135)) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621679607298Sym0 :: TyFun (Maybe (a6989586621679544134 ~> b6989586621679544135)) (Maybe a6989586621679544134 ~> Maybe b6989586621679544135) -> Type) (a6989586621679607296 :: Maybe (a6989586621679544134 ~> b6989586621679544135)) = TFHelper_6989586621679607298Sym1 a6989586621679607296
type Apply (TFHelper_6989586621679607328Sym0 :: TyFun (Maybe a6989586621679544139) (Maybe b6989586621679544140 ~> Maybe b6989586621679544140) -> Type) (a6989586621679607326 :: Maybe a6989586621679544139) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621679607328Sym0 :: TyFun (Maybe a6989586621679544139) (Maybe b6989586621679544140 ~> Maybe b6989586621679544140) -> Type) (a6989586621679607326 :: Maybe a6989586621679544139) = (TFHelper_6989586621679607328Sym1 a6989586621679607326 b6989586621679544140 :: TyFun (Maybe b6989586621679544140) (Maybe b6989586621679544140) -> Type)
type Apply (TFHelper_6989586621679607486Sym0 :: TyFun (Maybe a6989586621679544159) (Maybe b6989586621679544160 ~> Maybe b6989586621679544160) -> Type) (a6989586621679607484 :: Maybe a6989586621679544159) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621679607486Sym0 :: TyFun (Maybe a6989586621679544159) (Maybe b6989586621679544160 ~> Maybe b6989586621679544160) -> Type) (a6989586621679607484 :: Maybe a6989586621679544159) = (TFHelper_6989586621679607486Sym1 a6989586621679607484 b6989586621679544160 :: TyFun (Maybe b6989586621679544160) (Maybe b6989586621679544160) -> Type)
type Apply (ShowsPrec_6989586621680280310Sym1 a6989586621680280307 a3530822107858468865 :: TyFun (Maybe a3530822107858468865) (Symbol ~> Symbol) -> Type) (a6989586621680280308 :: Maybe a3530822107858468865) 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowsPrec_6989586621680280310Sym1 a6989586621680280307 a3530822107858468865 :: TyFun (Maybe a3530822107858468865) (Symbol ~> Symbol) -> Type) (a6989586621680280308 :: Maybe a3530822107858468865) = ShowsPrec_6989586621680280310Sym2 a6989586621680280307 a6989586621680280308
type Apply (TFHelper_6989586621679607470Sym0 :: TyFun (Maybe a6989586621679544157) ((a6989586621679544157 ~> Maybe b6989586621679544158) ~> Maybe b6989586621679544158) -> Type) (a6989586621679607468 :: Maybe a6989586621679544157) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621679607470Sym0 :: TyFun (Maybe a6989586621679544157) ((a6989586621679544157 ~> Maybe b6989586621679544158) ~> Maybe b6989586621679544158) -> Type) (a6989586621679607468 :: Maybe a6989586621679544157) = (TFHelper_6989586621679607470Sym1 a6989586621679607468 b6989586621679544158 :: TyFun (a6989586621679544157 ~> Maybe b6989586621679544158) (Maybe b6989586621679544158) -> Type)
type Apply (LiftA2_6989586621679607314Sym1 a6989586621679607311 :: TyFun (Maybe a6989586621679544136) (Maybe b6989586621679544137 ~> Maybe c6989586621679544138) -> Type) (a6989586621679607312 :: Maybe a6989586621679544136) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (LiftA2_6989586621679607314Sym1 a6989586621679607311 :: TyFun (Maybe a6989586621679544136) (Maybe b6989586621679544137 ~> Maybe c6989586621679544138) -> Type) (a6989586621679607312 :: Maybe a6989586621679544136) = LiftA2_6989586621679607314Sym2 a6989586621679607311 a6989586621679607312
type Apply (Let6989586621680451027MfSym2 xs6989586621680451026 f6989586621680451025 :: TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) (a6989586621680451028 :: Maybe k2) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680451027MfSym2 xs6989586621680451026 f6989586621680451025 :: TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) (a6989586621680451028 :: Maybe k2) = Let6989586621680451027MfSym3 xs6989586621680451026 f6989586621680451025 a6989586621680451028
type Apply (FindSym0 :: TyFun (a6989586621679939159 ~> Bool) ([a6989586621679939159] ~> Maybe a6989586621679939159) -> Type) (a6989586621679948716 :: a6989586621679939159 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FindSym0 :: TyFun (a6989586621679939159 ~> Bool) ([a6989586621679939159] ~> Maybe a6989586621679939159) -> Type) (a6989586621679948716 :: a6989586621679939159 ~> Bool) = FindSym1 a6989586621679948716
type Apply (FindIndexSym0 :: TyFun (a6989586621679939156 ~> Bool) ([a6989586621679939156] ~> Maybe Nat) -> Type) (a6989586621679949076 :: a6989586621679939156 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FindIndexSym0 :: TyFun (a6989586621679939156 ~> Bool) ([a6989586621679939156] ~> Maybe Nat) -> Type) (a6989586621679949076 :: a6989586621679939156 ~> Bool) = FindIndexSym1 a6989586621679949076
type Apply (MapMaybeSym0 :: TyFun (a6989586621679494596 ~> Maybe b6989586621679494597) ([a6989586621679494596] ~> [b6989586621679494597]) -> Type) (a6989586621679494763 :: a6989586621679494596 ~> Maybe b6989586621679494597) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (MapMaybeSym0 :: TyFun (a6989586621679494596 ~> Maybe b6989586621679494597) ([a6989586621679494596] ~> [b6989586621679494597]) -> Type) (a6989586621679494763 :: a6989586621679494596 ~> Maybe b6989586621679494597) = MapMaybeSym1 a6989586621679494763
type Apply (Fmap_6989586621679607137Sym0 :: TyFun (a6989586621679544128 ~> b6989586621679544129) (Maybe a6989586621679544128 ~> Maybe b6989586621679544129) -> Type) (a6989586621679607135 :: a6989586621679544128 ~> b6989586621679544129) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (Fmap_6989586621679607137Sym0 :: TyFun (a6989586621679544128 ~> b6989586621679544129) (Maybe a6989586621679544128 ~> Maybe b6989586621679544129) -> Type) (a6989586621679607135 :: a6989586621679544128 ~> b6989586621679544129) = Fmap_6989586621679607137Sym1 a6989586621679607135
type Apply (UnfoldrSym0 :: TyFun (b6989586621679939215 ~> Maybe (a6989586621679939216, b6989586621679939215)) (b6989586621679939215 ~> [a6989586621679939216]) -> Type) (a6989586621679949149 :: b6989586621679939215 ~> Maybe (a6989586621679939216, b6989586621679939215)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (UnfoldrSym0 :: TyFun (b6989586621679939215 ~> Maybe (a6989586621679939216, b6989586621679939215)) (b6989586621679939215 ~> [a6989586621679939216]) -> Type) (a6989586621679949149 :: b6989586621679939215 ~> Maybe (a6989586621679939216, b6989586621679939215)) = UnfoldrSym1 a6989586621679949149
type Apply (FindSym0 :: TyFun (a6989586621680450093 ~> Bool) (t6989586621680450092 a6989586621680450093 ~> Maybe a6989586621680450093) -> Type) (a6989586621680450550 :: a6989586621680450093 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FindSym0 :: TyFun (a6989586621680450093 ~> Bool) (t6989586621680450092 a6989586621680450093 ~> Maybe a6989586621680450093) -> Type) (a6989586621680450550 :: a6989586621680450093 ~> Bool) = (FindSym1 a6989586621680450550 t6989586621680450092 :: TyFun (t6989586621680450092 a6989586621680450093) (Maybe a6989586621680450093) -> Type)
type Apply (Let6989586621679494770RsSym0 :: TyFun (a6989586621679494596 ~> Maybe k1) (TyFun k (TyFun [a6989586621679494596] [k1] -> Type) -> Type) -> Type) (f6989586621679494767 :: a6989586621679494596 ~> Maybe k1) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (Let6989586621679494770RsSym0 :: TyFun (a6989586621679494596 ~> Maybe k1) (TyFun k (TyFun [a6989586621679494596] [k1] -> Type) -> Type) -> Type) (f6989586621679494767 :: a6989586621679494596 ~> Maybe k1) = (Let6989586621679494770RsSym1 f6989586621679494767 :: TyFun k (TyFun [a6989586621679494596] [k1] -> Type) -> Type)
type Apply (Let6989586621680451002MfSym0 :: TyFun (k3 ~> (k2 ~> k3)) (TyFun k (TyFun k3 (TyFun (Maybe k2) (Maybe k3) -> Type) -> Type) -> Type) -> Type) (f6989586621680451000 :: k3 ~> (k2 ~> k3)) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680451002MfSym0 :: TyFun (k3 ~> (k2 ~> k3)) (TyFun k (TyFun k3 (TyFun (Maybe k2) (Maybe k3) -> Type) -> Type) -> Type) -> Type) (f6989586621680451000 :: k3 ~> (k2 ~> k3)) = (Let6989586621680451002MfSym1 f6989586621680451000 :: TyFun k (TyFun k3 (TyFun (Maybe k2) (Maybe k3) -> Type) -> Type) -> Type)
type Apply (Let6989586621680451027MfSym0 :: TyFun (k2 ~> (k3 ~> k3)) (TyFun k (TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) -> Type) -> Type) (f6989586621680451025 :: k2 ~> (k3 ~> k3)) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680451027MfSym0 :: TyFun (k2 ~> (k3 ~> k3)) (TyFun k (TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) -> Type) -> Type) (f6989586621680451025 :: k2 ~> (k3 ~> k3)) = (Let6989586621680451027MfSym1 f6989586621680451025 :: TyFun k (TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) -> Type)
type Apply (Traverse_6989586621680753858Sym0 :: TyFun (a6989586621680747697 ~> f6989586621680747696 b6989586621680747698) (Maybe a6989586621680747697 ~> f6989586621680747696 (Maybe b6989586621680747698)) -> Type) (a6989586621680753856 :: a6989586621680747697 ~> f6989586621680747696 b6989586621680747698) 
Instance details

Defined in Data.Singletons.Prelude.Traversable

type Apply (Traverse_6989586621680753858Sym0 :: TyFun (a6989586621680747697 ~> f6989586621680747696 b6989586621680747698) (Maybe a6989586621680747697 ~> f6989586621680747696 (Maybe b6989586621680747698)) -> Type) (a6989586621680753856 :: a6989586621680747697 ~> f6989586621680747696 b6989586621680747698) = Traverse_6989586621680753858Sym1 a6989586621680753856
type Apply (Maybe_Sym1 a6989586621679493192 a6989586621679493175 :: TyFun (a6989586621679493175 ~> b6989586621679493174) (Maybe a6989586621679493175 ~> b6989586621679493174) -> Type) (a6989586621679493193 :: a6989586621679493175 ~> b6989586621679493174) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (Maybe_Sym1 a6989586621679493192 a6989586621679493175 :: TyFun (a6989586621679493175 ~> b6989586621679493174) (Maybe a6989586621679493175 ~> b6989586621679493174) -> Type) (a6989586621679493193 :: a6989586621679493175 ~> b6989586621679493174) = Maybe_Sym2 a6989586621679493192 a6989586621679493193
type Apply (LiftA2_6989586621679607314Sym0 :: TyFun (a6989586621679544136 ~> (b6989586621679544137 ~> c6989586621679544138)) (Maybe a6989586621679544136 ~> (Maybe b6989586621679544137 ~> Maybe c6989586621679544138)) -> Type) (a6989586621679607311 :: a6989586621679544136 ~> (b6989586621679544137 ~> c6989586621679544138)) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (LiftA2_6989586621679607314Sym0 :: TyFun (a6989586621679544136 ~> (b6989586621679544137 ~> c6989586621679544138)) (Maybe a6989586621679544136 ~> (Maybe b6989586621679544137 ~> Maybe c6989586621679544138)) -> Type) (a6989586621679607311 :: a6989586621679544136 ~> (b6989586621679544137 ~> c6989586621679544138)) = LiftA2_6989586621679607314Sym1 a6989586621679607311
type Apply (Lambda_6989586621680338268Sym1 a6989586621680338266 :: TyFun (k1 ~> First a) (TyFun k1 (Maybe a) -> Type) -> Type) (k6989586621680338267 :: k1 ~> First a) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (Lambda_6989586621680338268Sym1 a6989586621680338266 :: TyFun (k1 ~> First a) (TyFun k1 (Maybe a) -> Type) -> Type) (k6989586621680338267 :: k1 ~> First a) = Lambda_6989586621680338268Sym2 a6989586621680338266 k6989586621680338267
type Apply (Lambda_6989586621680338356Sym1 a6989586621680338354 :: TyFun (k1 ~> Last a) (TyFun k1 (Maybe a) -> Type) -> Type) (k6989586621680338355 :: k1 ~> Last a) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (Lambda_6989586621680338356Sym1 a6989586621680338354 :: TyFun (k1 ~> Last a) (TyFun k1 (Maybe a) -> Type) -> Type) (k6989586621680338355 :: k1 ~> Last a) = Lambda_6989586621680338356Sym2 a6989586621680338354 k6989586621680338355
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 #

newtype ContractAddr (cp :: Type) Source #

Since Contract name is used to designate contract code, lets call analogy of TContract type as follows.

Constructors

ContractAddr 
Instances
IsoValue (ContractAddr cp) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (ContractAddr cp) :: T Source #

type ToT (ContractAddr cp) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT (ContractAddr cp) = TContract (ToT cp)

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.

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

Default a => Default (Parser a) Source # 
Instance details

Defined in Michelson.Parser.Types

Methods

def :: Parser 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 #

Default (BigMap k v) Source # 
Instance details

Defined in Michelson.Typed.Haskell.Value

Methods

def :: BigMap 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) #