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

Lorentz.Value

Description

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

Synopsis

Documentation

class WellTypedToT a => IsoValue a where #

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 #

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

type ToT a = GValueType (Rep a) #

Methods

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

Converts a Haskell structure into Value representation.

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

Converts a Value into Haskell type.

Instances

Instances details
IsoValue Bool 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Bool :: T #

Methods

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

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

IsoValue Integer 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Integer :: T #

IsoValue Natural 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Natural :: T #

IsoValue () 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT () :: T #

Methods

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

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

IsoValue ByteString 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT ByteString :: T #

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

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Text :: T #

Methods

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

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

IsoValue MyCompoundType 
Instance details

Defined in Michelson.Typed.Haskell.Instr.Sum

Associated Types

type ToT MyCompoundType :: T #

IsoValue Operation 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Operation :: T #

IsoValue EpAddress 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT EpAddress :: T #

IsoValue Address 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Address :: T #

IsoValue Mutez 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Mutez :: T #

IsoValue Timestamp 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Timestamp :: T #

IsoValue ChainId 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT ChainId :: T #

IsoValue PublicKey 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT PublicKey :: T #

IsoValue Signature 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Signature :: T #

IsoValue KeyHash 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT KeyHash :: T #

IsoValue MText 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT MText :: T #

IsoValue MyType2 
Instance details

Defined in Michelson.Typed.Haskell.Instr.Product

Associated Types

type ToT MyType2 :: T #

Methods

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

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

IsoValue MyType 
Instance details

Defined in Michelson.Typed.Haskell.Instr.Sum

Associated Types

type ToT MyType :: T #

Methods

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

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

IsoValue MyType' 
Instance details

Defined in Michelson.Typed.Haskell.Instr.Sum

Associated Types

type ToT MyType' :: T #

Methods

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

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

IsoValue MyEnum 
Instance details

Defined in Michelson.Typed.Haskell.Instr.Sum

Associated Types

type ToT MyEnum :: T #

Methods

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

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

IsoValue MyTypeWithNamedField 
Instance details

Defined in Michelson.Typed.Haskell.Instr.Sum

Associated Types

type ToT MyTypeWithNamedField :: T #

Methods

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

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

IsoValue UnspecifiedError Source # 
Instance details

Defined in Lorentz.Errors

Associated Types

type ToT UnspecifiedError :: T #

IsoValue Empty Source # 
Instance details

Defined in Lorentz.Empty

Associated Types

type ToT Empty :: T #

IsoValue a => IsoValue [a] 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT [a] :: T #

Methods

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

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

IsoValue a => IsoValue (Maybe a) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (Maybe a) :: T #

Methods

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

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

IsoValue a => IsoValue (Identity a) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (Identity a) :: T #

Methods

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

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

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

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (Set c) :: T #

Methods

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

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

WellTypedToT arg => IsoValue (ContractRef arg) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (ContractRef arg) :: T #

Methods

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

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

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

Defined in Lorentz.EntryPoints.Helpers

Associated Types

type ToT (ShouldHaveEntryPoints r) :: T #

IsoValue (FutureContract arg) Source # 
Instance details

Defined in Lorentz.Address

Associated Types

type ToT (FutureContract arg) :: T #

IsoValue (UStore a) Source # 
Instance details

Defined in Lorentz.UStore.Types

Associated Types

type ToT (UStore a) :: T #

Methods

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

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

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

This instance cannot be implemented, use IsError instance instead.

Instance details

Defined in Lorentz.Errors

Associated Types

type ToT (CustomError tag) :: T #

Methods

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

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

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

Defined in Lorentz.Macro

Associated Types

type ToT (VoidResult r) :: T #

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

Defined in Lorentz.Store

Associated Types

type ToT (Store a) :: T #

Methods

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

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

IsoValue (UParam entries) Source # 
Instance details

Defined in Lorentz.UParam

Associated Types

type ToT (UParam entries) :: T #

Methods

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

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

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

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (Either l r) :: T #

Methods

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

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

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

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (a, b) :: T #

Methods

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

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

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

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (Map k v) :: T #

Methods

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

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

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

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (BigMap k v) :: T #

Methods

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

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

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

Defined in Lorentz.EntryPoints.Manual

Associated Types

type ToT (ParameterWrapper deriv cp) :: T #

Methods

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

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

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

Defined in Lorentz.Zip

Associated Types

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

Methods

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

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

IsoValue (TAddress p) Source # 
Instance details

Defined in Lorentz.Address

Associated Types

type ToT (TAddress p) :: T #

Methods

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

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

IsoValue (MigrationScript oldStore newStore) Source # 
Instance details

Defined in Lorentz.UStore.Migration.Base

Associated Types

type ToT (MigrationScript oldStore newStore) :: T #

Methods

toVal :: MigrationScript oldStore newStore -> Value (ToT (MigrationScript oldStore newStore)) #

fromVal :: Value (ToT (MigrationScript oldStore newStore)) -> MigrationScript oldStore newStore #

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

Defined in Lorentz.Macro

Associated Types

type ToT (Void_ a r) :: T #

Methods

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

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

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

Defined in Lorentz.Macro

Associated Types

type ToT (View a r) :: T #

Methods

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

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

IsoValue (Extensible x) Source # 
Instance details

Defined in Lorentz.Extensible

Associated Types

type ToT (Extensible x) :: T #

(WellTypedIsoValue st, WellTypedIsoValue o) => IsoValue (StorageSkeleton st o) Source # 
Instance details

Defined in Lorentz.Store

Associated Types

type ToT (StorageSkeleton st o) :: T #

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

Defined in Michelson.Typed.Haskell.Value

Associated Types

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

Methods

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

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

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

Defined in Michelson.Typed.Haskell.Value

Associated Types

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

Methods

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

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

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

Defined in Michelson.Typed.Haskell.Value

Associated Types

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

Methods

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

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

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

Defined in Lorentz.Store

Associated Types

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

Methods

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

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

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

Defined in Michelson.Typed.Haskell.Value

Associated Types

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

Methods

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

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

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

Defined in Lorentz.UStore.Migration.Base

Associated Types

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

Methods

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

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

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

Defined in Michelson.Typed.Haskell.Value

Associated Types

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

Methods

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

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

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

Defined in Michelson.Typed.Haskell.Value

Associated Types

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

Methods

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

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

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

Defined in Michelson.Typed.Haskell.Value

Associated Types

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

Methods

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

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

Primitive types

data Integer #

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

Useful properties resulting from the invariants:

Instances

Instances details
Enum Integer

Since: base-2.1

Instance details

Defined in GHC.Enum

Eq Integer 
Instance details

Defined in GHC.Integer.Type

Methods

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

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

Integral Integer

Since: base-2.0.1

Instance details

Defined in GHC.Real

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 :: forall r r'. (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

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 #

NFData Integer 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Integer -> () #

Hashable Integer 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Integer -> Int #

hash :: Integer -> Int #

ToJSON Integer 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON TezosBigNum 
Instance details

Defined in Morley.Micheline.Json

ToJSONKey Integer 
Instance details

Defined in Data.Aeson.Types.ToJSON

FromJSON TezosBigNum 
Instance details

Defined in Morley.Micheline.Json

Subtractive Integer 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

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

TypeHasDoc Integer 
Instance details

Defined in Michelson.Typed.Haskell.Doc

IsoValue Integer 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Integer :: T #

Pretty Integer 
Instance details

Defined in Text.PrettyPrint.Annotated.WL

Methods

pretty :: Integer -> Doc b #

prettyList :: [Integer] -> Doc b #

Pretty Rational 
Instance details

Defined in Text.PrettyPrint.Annotated.WL

Methods

pretty :: Rational -> Doc b #

prettyList :: [Rational] -> Doc b #

Pretty Integer 
Instance details

Defined in Text.PrettyPrint.Leijen.Text

Methods

pretty :: Integer -> Doc #

prettyList :: [Integer] -> Doc #

HasTypeAnn Integer Source # 
Instance details

Defined in Lorentz.TypeAnns

NonZero Integer Source # 
Instance details

Defined in Lorentz.Instr

Methods

nonZero :: forall (s :: [Type]). (Integer ': s) :-> (Maybe Integer ': s) 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

UnaryArithOpHs Abs Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Abs Integer Source #

UnaryArithOpHs Neg Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Neg Integer Source #

UnaryArithOpHs Not Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Not Integer Source #

UnaryArithOpHs Eq' Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Eq' Integer Source #

UnaryArithOpHs Neq Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Neq Integer Source #

UnaryArithOpHs Lt Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Lt Integer Source #

UnaryArithOpHs Gt Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Gt Integer Source #

UnaryArithOpHs Le Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Le Integer Source #

UnaryArithOpHs Ge Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Ge Integer Source #

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

Defined in Data.Reflection

Methods

reflect :: proxy n -> Integer #

ArithOpHs Add Integer Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Integer Integer Source #

ArithOpHs Add Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Integer Natural Source #

ArithOpHs Add Integer Timestamp Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Integer Timestamp Source #

ArithOpHs Add Natural Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Natural Integer Source #

ArithOpHs Add Timestamp Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Timestamp Integer Source #

ArithOpHs Sub Integer Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Sub Integer Integer Source #

ArithOpHs Sub Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Sub Integer Natural Source #

ArithOpHs Sub Natural Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Sub Natural Integer Source #

ArithOpHs Sub Timestamp Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Sub Timestamp Integer Source #

ArithOpHs Mul Integer Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Integer Integer Source #

ArithOpHs Mul Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Integer Natural Source #

ArithOpHs Mul Natural Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Natural Integer Source #

ArithOpHs And Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs And Integer Natural Source #

() :=> (Enum Integer) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Enum Integer #

() :=> (Eq Integer) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Eq Integer #

() :=> (Integral Integer) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Integral Integer #

() :=> (Num Integer) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Num Integer #

() :=> (Ord Integer) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Ord Integer #

() :=> (Real Integer) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Real Integer #

() :=> (Bits Integer) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Bits Integer #

type Difference Integer 
Instance details

Defined in Basement.Numerical.Subtractive

type TypeDocFieldDescriptions Integer 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type ToT Integer 
Instance details

Defined in Michelson.Typed.Haskell.Value

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

Defined in Lorentz.Polymorphic

type EDivOpResHs Integer Natural Source # 
Instance details

Defined in Lorentz.Polymorphic

type EDivOpResHs Natural Integer Source # 
Instance details

Defined in Lorentz.Polymorphic

type EModOpResHs Integer Integer Source # 
Instance details

Defined in Lorentz.Polymorphic

type EModOpResHs Integer Natural Source # 
Instance details

Defined in Lorentz.Polymorphic

type EModOpResHs Natural Integer Source # 
Instance details

Defined in Lorentz.Polymorphic

type UnaryArithResHs Abs Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Neg Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Not Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Eq' Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Neq Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Lt Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Gt Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Le Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Ge Integer Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Add Integer Integer Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Add Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Add Integer Timestamp Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Add Natural Integer Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Add Timestamp Integer Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs 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 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 And Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

data Natural #

Type representing arbitrary-precision non-negative integers.

>>> 2^100 :: Natural
1267650600228229401496703205376

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

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

Since: base-4.8.0.0

Instances

Instances details
Enum Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Enum

Eq Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Natural

Methods

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

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

Integral Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Real

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 :: forall r r'. (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

Lift Natural 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Natural -> Q Exp #

NFData Natural

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Natural -> () #

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

Subtractive Natural 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Natural #

TypeHasDoc Natural 
Instance details

Defined in Michelson.Typed.Haskell.Doc

IsoValue Natural 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Natural :: T #

Pretty Natural 
Instance details

Defined in Text.PrettyPrint.Annotated.WL

Methods

pretty :: Natural -> Doc b #

prettyList :: [Natural] -> Doc b #

HasTypeAnn Natural Source # 
Instance details

Defined in Lorentz.TypeAnns

NonZero Natural Source # 
Instance details

Defined in Lorentz.Instr

Methods

nonZero :: forall (s :: [Type]). (Natural ': s) :-> (Maybe Natural ': s) 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

UnaryArithOpHs Neg Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Neg Natural Source #

UnaryArithOpHs Not Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Not Natural Source #

ArithOpHs Add Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Integer Natural Source #

ArithOpHs Add Natural Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Natural Integer Source #

ArithOpHs Add Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Natural Natural Source #

ArithOpHs Sub Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Sub Integer Natural Source #

ArithOpHs Sub Natural Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Sub Natural Integer Source #

ArithOpHs Sub Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Sub Natural Natural Source #

ArithOpHs Mul Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Integer Natural Source #

ArithOpHs Mul Natural Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Natural Integer Source #

ArithOpHs Mul Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Natural Natural Source #

ArithOpHs Mul Natural Mutez Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Natural Mutez Source #

ArithOpHs Mul Mutez Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Mutez Natural Source #

ArithOpHs Or Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Or Natural Natural Source #

ArithOpHs And Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs And Integer Natural Source #

ArithOpHs And Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs And Natural Natural Source #

ArithOpHs Xor Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Xor Natural Natural Source #

ArithOpHs Lsl Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Lsl Natural Natural Source #

ArithOpHs Lsr Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Lsr Natural Natural Source #

() :=> (Enum Natural) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Enum Natural #

() :=> (Eq Natural) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Eq Natural #

() :=> (Integral Natural) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Integral Natural #

() :=> (Num Natural) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Num Natural #

() :=> (Ord Natural) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Ord Natural #

() :=> (Read Natural) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Read Natural #

() :=> (Real Natural) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Real Natural #

() :=> (Show Natural) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Show Natural #

() :=> (Bits Natural) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Bits Natural #

type Difference Natural 
Instance details

Defined in Basement.Numerical.Subtractive

type TypeDocFieldDescriptions Natural 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type ToT Natural 
Instance details

Defined in Michelson.Typed.Haskell.Value

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

Defined in Lorentz.Polymorphic

type EDivOpResHs Natural Integer Source # 
Instance details

Defined in Lorentz.Polymorphic

type EDivOpResHs Natural Natural Source # 
Instance details

Defined in Lorentz.Polymorphic

type EDivOpResHs Mutez Natural Source # 
Instance details

Defined in Lorentz.Polymorphic

type EModOpResHs Integer Natural Source # 
Instance details

Defined in Lorentz.Polymorphic

type EModOpResHs Natural Integer Source # 
Instance details

Defined in Lorentz.Polymorphic

type EModOpResHs Natural Natural Source # 
Instance details

Defined in Lorentz.Polymorphic

type EModOpResHs Mutez Natural Source # 
Instance details

Defined in Lorentz.Polymorphic

type UnaryArithResHs Neg Natural Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Not Natural Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Add Integer Natural Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Add Natural Integer Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Add Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

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

Defined in Lorentz.Arith

type ArithResHs Lsl Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Lsr Natural Natural Source # 
Instance details

Defined in Lorentz.Arith

data MText #

Michelson string value.

This is basically a mere text with limits imposed by the language: https://tezos.gitlab.io/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

Instances details
Eq MText 
Instance details

Defined in Michelson.Text

Methods

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

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

Data MText 
Instance details

Defined in Michelson.Text

Methods

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

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

toConstr :: MText -> Constr #

dataTypeOf :: MText -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord MText 
Instance details

Defined in Michelson.Text

Methods

compare :: MText -> MText -> Ordering #

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

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

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

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

max :: MText -> MText -> MText #

min :: MText -> MText -> MText #

Show MText 
Instance details

Defined in Michelson.Text

Methods

showsPrec :: Int -> MText -> ShowS #

show :: MText -> String #

showList :: [MText] -> ShowS #

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

Defined in Michelson.Text

Methods

fromString :: String -> MText #

Generic MText 
Instance details

Defined in Michelson.Text

Associated Types

type Rep MText :: Type -> Type #

Methods

from :: MText -> Rep MText x #

to :: Rep MText x -> MText #

Semigroup MText 
Instance details

Defined in Michelson.Text

Methods

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

sconcat :: NonEmpty MText -> MText #

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

Monoid MText 
Instance details

Defined in Michelson.Text

Methods

mempty :: MText #

mappend :: MText -> MText -> MText #

mconcat :: [MText] -> MText #

Arbitrary MText 
Instance details

Defined in Michelson.Text

Methods

arbitrary :: Gen MText #

shrink :: MText -> [MText] #

NFData MText 
Instance details

Defined in Michelson.Text

Methods

rnf :: MText -> () #

Hashable MText 
Instance details

Defined in Michelson.Text

Methods

hashWithSalt :: Int -> MText -> Int #

hash :: MText -> Int #

ToJSON MText 
Instance details

Defined in Michelson.Text

FromJSON MText 
Instance details

Defined in Michelson.Text

Buildable MText 
Instance details

Defined in Michelson.Text

Methods

build :: MText -> Builder #

TypeHasDoc MText 
Instance details

Defined in Michelson.Typed.Haskell.Doc

IsoValue MText 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT MText :: T #

HasCLReader MText 
Instance details

Defined in Michelson.Text

Container MText 
Instance details

Defined in Michelson.Text

Associated Types

type Element MText #

Methods

toList :: MText -> [Element MText] #

null :: MText -> Bool #

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

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

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

length :: MText -> Int #

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

maximum :: MText -> Element MText #

minimum :: MText -> Element MText #

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

fold :: MText -> Element MText #

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

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

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

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

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

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

and :: MText -> Bool #

or :: MText -> Bool #

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

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

ToText MText 
Instance details

Defined in Michelson.Text

Methods

toText :: MText -> Text #

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

HasTypeAnn MText Source # 
Instance details

Defined in Lorentz.TypeAnns

ErrorHasDoc MText Source # 
Instance details

Defined in Lorentz.Errors

Associated Types

type ErrorRequirements MText Source #

IsError MText Source #

Use this for internal errors only.

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

Instance details

Defined in Lorentz.Errors

Methods

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

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

type Rep MText 
Instance details

Defined in Michelson.Text

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

Defined in Michelson.Typed.Haskell.Doc

type ToT MText 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT MText = 'TString
type Element MText 
Instance details

Defined in Michelson.Text

type ErrorRequirements MText Source # 
Instance details

Defined in Lorentz.Errors

data Bool #

Constructors

False 
True 

Instances

Instances details
Bounded Bool

Since: base-2.1

Instance details

Defined in GHC.Enum

Enum Bool

Since: base-2.1

Instance details

Defined in GHC.Enum

Methods

succ :: Bool -> Bool #

pred :: Bool -> Bool #

toEnum :: Int -> Bool #

fromEnum :: Bool -> Int #

enumFrom :: Bool -> [Bool] #

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

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

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

Eq Bool 
Instance details

Defined in GHC.Classes

Methods

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

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

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 :: forall r r'. (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 #

Generic Bool

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep Bool :: Type -> Type #

Methods

from :: Bool -> Rep Bool x #

to :: Rep Bool x -> Bool #

Lift Bool 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Bool -> Q Exp #

Assertable Bool 
Instance details

Defined in Test.HUnit.Base

Methods

assert :: Bool -> Assertion #

AssertionPredicable Bool 
Instance details

Defined in Test.HUnit.Base

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 #

NFData Bool 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Bool -> () #

Hashable Bool 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Bool -> Int #

hash :: Bool -> Int #

ToJSON Bool 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Bool 
Instance details

Defined in Data.Aeson.Types.ToJSON

SingKind Bool

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type DemoteRep Bool

Methods

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

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

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 #

Unbox Bool 
Instance details

Defined in Data.Vector.Unboxed.Base

TypeHasDoc Bool 
Instance details

Defined in Michelson.Typed.Haskell.Doc

IsoValue Bool 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Bool :: T #

Methods

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

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

Variate Bool 
Instance details

Defined in System.Random.MWC

Methods

uniform :: PrimMonad m => Gen (PrimState m) -> m Bool #

uniformR :: PrimMonad m => (Bool, Bool) -> Gen (PrimState m) -> m Bool #

PShow Bool 
Instance details

Defined in Data.Singletons.Prelude.Show

Associated Types

type ShowsPrec arg0 arg1 arg2 :: Symbol #

type Show_ arg0 :: Symbol #

type ShowList arg0 arg1 :: Symbol #

SShow Bool 
Instance details

Defined in Data.Singletons.Prelude.Show

Methods

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

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

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

PEnum Bool 
Instance details

Defined in Data.Singletons.Prelude.Enum

Associated Types

type Succ arg0 :: a0 #

type Pred arg0 :: a0 #

type ToEnum arg0 :: a0 #

type FromEnum arg0 :: Nat #

type EnumFromTo arg0 arg1 :: [a0] #

type EnumFromThenTo arg0 arg1 arg2 :: [a0] #

SEnum Bool 
Instance details

Defined in Data.Singletons.Prelude.Enum

Methods

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

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

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

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

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

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

PBounded Bool 
Instance details

Defined in Data.Singletons.Prelude.Enum

Associated Types

type MinBound :: a0 #

type MaxBound :: a0 #

SBounded Bool 
Instance details

Defined in Data.Singletons.Prelude.Enum

POrd Bool 
Instance details

Defined in Data.Singletons.Prelude.Ord

Associated Types

type Compare arg0 arg1 :: Ordering #

type arg0 < arg1 :: Bool #

type arg0 <= arg1 :: Bool #

type arg0 > arg1 :: Bool #

type arg0 >= arg1 :: Bool #

type Max arg0 arg1 :: a0 #

type Min arg0 arg1 :: a0 #

SOrd Bool 
Instance details

Defined in Data.Singletons.Prelude.Ord

Methods

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

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

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

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

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

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

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

SEq Bool 
Instance details

Defined in Data.Singletons.Prelude.Eq

Methods

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

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

PEq Bool 
Instance details

Defined in Data.Singletons.Prelude.Eq

Associated Types

type x == y :: Bool #

type x /= y :: Bool #

Pretty Bool 
Instance details

Defined in Text.PrettyPrint.Annotated.WL

Methods

pretty :: Bool -> Doc b #

prettyList :: [Bool] -> Doc b #

Pretty Bool 
Instance details

Defined in Text.PrettyPrint.Leijen.Text

Methods

pretty :: Bool -> Doc #

prettyList :: [Bool] -> Doc #

HasTypeAnn Bool Source # 
Instance details

Defined in Lorentz.TypeAnns

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

TestCoercion SBool 
Instance details

Defined in Data.Singletons.Prelude.Instances

Methods

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

TestEquality SBool 
Instance details

Defined in Data.Singletons.Prelude.Instances

Methods

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

Vector Vector Bool 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Bool 
Instance details

Defined in Data.Vector.Unboxed.Base

UnaryArithOpHs Not Bool Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Not Bool Source #

ArithOpHs Or Bool Bool Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Or Bool Bool Source #

ArithOpHs And Bool Bool Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs And Bool Bool Source #

ArithOpHs Xor Bool Bool Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Xor Bool Bool Source #

() :=> (Bounded Bool) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Bounded Bool #

() :=> (Enum Bool) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Enum Bool #

() :=> (Eq Bool) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Eq Bool #

() :=> (Ord Bool) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Ord Bool #

() :=> (Read Bool) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Read Bool #

() :=> (Show Bool) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Show Bool #

() :=> (Bits Bool) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Bits Bool #

Example (a -> Bool) 
Instance details

Defined in Test.Hspec.Core.Example

Associated Types

type Arg (a -> Bool) #

Methods

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

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

Defined in Data.Singletons.Prelude.Bool

SuppressUnusedWarnings FromEnum_6989586621680152586Sym0 
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_6989586621679803720Sym0 
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_6989586621680152573Sym0 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings ShowsPrec_6989586621680595859Sym0 
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 x => SingI ((||@#@$$) x :: TyFun Bool Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Bool

Methods

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

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

Defined in Data.Singletons.Prelude.Bool

Methods

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

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

Defined in Data.Singletons.TypeLits.Internal

Methods

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

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

Defined in Data.Singletons.Prelude.Monad.Internal

Methods

sing :: Sing GuardSym0 #

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

Defined in Data.Singletons.Prelude.Monad

Methods

sing :: Sing UnlessSym0 #

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

Defined in Data.Singletons.Prelude.Monad.Internal

Methods

sing :: Sing WhenSym0 #

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

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

Methods

sing :: Sing ListnullSym0 #

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

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

Methods

sing :: Sing ListisPrefixOfSym0 #

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

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing NullSym0 #

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.Maybe

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

Defined in Data.Singletons.Prelude.Maybe

Methods

sing :: Sing IsJustSym0 #

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

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

Methods

sing :: Sing ListelemSym0 #

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

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing NotElemSym0 #

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

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing ElemSym0 #

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

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing OrSym0 #

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

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing AndSym0 #

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

Defined in Data.Singletons.Prelude.Eq

Methods

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

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

Defined in Data.Singletons.Prelude.Eq

Methods

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

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

Defined in Data.Singletons.Prelude.Bool

Methods

sing :: Sing Bool_Sym0 #

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

Defined in Data.Singletons.Prelude.Ord

Methods

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

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

Defined in Data.Singletons.Prelude.Ord

Methods

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

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

Defined in Data.Singletons.Prelude.Ord

Methods

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

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

Defined in Data.Singletons.Prelude.Ord

Methods

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

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

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

Methods

sing :: Sing ListtakeWhileSym0 #

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

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

Methods

sing :: Sing ListspanSym0 #

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

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

Methods

sing :: Sing ListpartitionSym0 #

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

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

Methods

sing :: Sing ListnubBySym0 #

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

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

Methods

sing :: Sing ListfilterSym0 #

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

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

Methods

sing :: Sing ListdropWhileSym0 #

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing SpanSym0 #

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

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing SelectSym0 #

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing NubBySym0 #

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing FindSym0 #

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing FilterSym0 #

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

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing Elem_bySym0 #

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing BreakSym0 #

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

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing AnySym0 #

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

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing AllSym0 #

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

Defined in Data.Singletons.Prelude.Base

Methods

sing :: Sing UntilSym0 #

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

Defined in Data.Singletons.Prelude.Bool

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

Defined in Data.Singletons.Prelude.Bool

SuppressUnusedWarnings (Compare_6989586621679803720Sym1 a6989586621679803718 :: TyFun Bool Ordering -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (ShowsPrec_6989586621680595859Sym1 a6989586621680595856 :: TyFun Bool (Symbol ~> Symbol) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Show

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

Defined in Data.Singletons.Prelude.Monad

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

Defined in Data.Singletons.Prelude.Monad.Internal

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

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

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

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

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.Maybe

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

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

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680742866Scrutinee_6989586621680742628Sym0 :: TyFun (t6989586621680742381 Bool) All -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680742857Scrutinee_6989586621680742630Sym0 :: TyFun (t6989586621680742381 Bool) Any -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Eq

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

Defined in Data.Singletons.Prelude.Eq

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

Defined in Data.Singletons.Prelude.Eq

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

Defined in Data.Singletons.Prelude.Bool

SuppressUnusedWarnings (TFHelper_6989586621679792578Sym0 :: TyFun a6989586621679792381 (a6989586621679792381 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (TFHelper_6989586621679792560Sym0 :: TyFun a6989586621679792381 (a6989586621679792381 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (TFHelper_6989586621679792542Sym0 :: TyFun a6989586621679792381 (a6989586621679792381 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (TFHelper_6989586621679792524Sym0 :: TyFun a6989586621679792381 (a6989586621679792381 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (Elem_6989586621680921217Sym0 :: TyFun a6989586621680742398 (Identity a6989586621680742398 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Identity

SuppressUnusedWarnings (Null_6989586621680921344Sym0 :: TyFun (Identity a6989586621680742396) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Identity

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.Base

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

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

Methods

sing :: Sing (ListisPrefixOfSym1 d) #

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

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

Methods

sing :: Sing (ListelemSym1 d) #

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

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (NotElemSym1 d) #

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

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (IsSuffixOfSym1 d) #

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

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (IsPrefixOfSym1 d) #

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

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (IsInfixOfSym1 d) #

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

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (ElemSym1 d) #

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

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (AnySym1 d) #

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

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (AllSym1 d) #

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

Defined in Data.Singletons.Prelude.Either

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

Defined in Data.Singletons.Prelude.Either

Methods

sing :: Sing IsLeftSym0 #

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

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (Elem_bySym1 d) #

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing ElemSym0 #

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

Defined in Data.Singletons.Prelude.Eq

Methods

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

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

Defined in Data.Singletons.Prelude.Eq

Methods

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

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

Defined in Data.Singletons.Prelude.Bool

Methods

sing :: Sing (Bool_Sym1 d) #

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

Defined in Data.Singletons.Prelude.Ord

Methods

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

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

Defined in Data.Singletons.Prelude.Ord

Methods

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

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

Defined in Data.Singletons.Prelude.Ord

Methods

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

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

Defined in Data.Singletons.Prelude.Ord

Methods

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

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

Defined in Data.Singletons.Prelude.Monad

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

Defined in Data.Singletons.Prelude.Monad

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

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing FindSym0 #

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

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing AnySym0 #

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

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing AllSym0 #

SuppressUnusedWarnings (ListisPrefixOfSym1 a6989586621680687765 :: TyFun [a6989586621680686805] Bool -> Type) 
Instance details

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

SuppressUnusedWarnings (ListelemSym1 a6989586621680687700 :: TyFun [a6989586621680686793] Bool -> Type) 
Instance details

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

SuppressUnusedWarnings (NotElemSym1 a6989586621680321269 :: TyFun [a6989586621680316399] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (IsSuffixOfSym1 a6989586621680321289 :: TyFun [a6989586621680316402] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (IsPrefixOfSym1 a6989586621680321295 :: TyFun [a6989586621680316403] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (IsInfixOfSym1 a6989586621680321283 :: TyFun [a6989586621680316401] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (ElemSym1 a6989586621680321276 :: TyFun [a6989586621680316400] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (AnySym1 a6989586621680321526 :: TyFun [a6989586621680316420] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (AllSym1 a6989586621680321533 :: TyFun [a6989586621680316421] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (IsRightSym0 :: TyFun (Either a6989586621680725232 b6989586621680725233) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Either

SuppressUnusedWarnings (IsLeftSym0 :: TyFun (Either a6989586621680725234 b6989586621680725235) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Either

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

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Elem_bySym1 a6989586621680320412 :: TyFun a6989586621680316317 ([a6989586621680316317] ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (NotElemSym0 :: TyFun a6989586621680742292 (t6989586621680742291 a6989586621680742292 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680744088Sym0 :: TyFun a6989586621680742398 (t6989586621680742381 a6989586621680742398 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680743921Sym0 :: TyFun a6989586621680742398 (t6989586621680742381 a6989586621680742398 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680743754Sym0 :: TyFun a6989586621680742398 (t6989586621680742381 a6989586621680742398 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680743413Sym0 :: TyFun a6989586621680742398 (t6989586621680742381 a6989586621680742398 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680743293Sym0 :: TyFun a6989586621680742398 (t6989586621680742381 a6989586621680742398 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (ElemSym0 :: TyFun a6989586621680742398 (t6989586621680742381 a6989586621680742398 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (DefaultEqSym1 a6989586621679774970 :: TyFun k6989586621679774969 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Eq

SuppressUnusedWarnings ((==@#@$$) x6989586621679774976 :: TyFun a6989586621679774975 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Eq

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

Defined in Data.Singletons.Prelude.Eq

SuppressUnusedWarnings (Bool_Sym1 a6989586621679771150 :: TyFun a6989586621679771144 (Bool ~> a6989586621679771144) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Bool

SuppressUnusedWarnings (TFHelper_6989586621679792578Sym1 a6989586621679792576 :: TyFun a6989586621679792381 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (TFHelper_6989586621679792560Sym1 a6989586621679792558 :: TyFun a6989586621679792381 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (TFHelper_6989586621679792542Sym1 a6989586621679792540 :: TyFun a6989586621679792381 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (TFHelper_6989586621679792524Sym1 a6989586621679792522 :: TyFun a6989586621679792381 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings ((>@#@$$) arg6989586621679792482 :: TyFun a6989586621679792381 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings ((>=@#@$$) arg6989586621679792486 :: TyFun a6989586621679792381 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings ((<@#@$$) arg6989586621679792474 :: TyFun a6989586621679792381 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (TFHelper_6989586621681108278Sym0 :: TyFun (Arg a6989586621681107123 b6989586621681107124) (Arg a6989586621681107123 b6989586621681107124 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

SuppressUnusedWarnings (Elem_6989586621680921217Sym1 a6989586621680921215 :: TyFun (Identity a6989586621680742398) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Identity

SuppressUnusedWarnings (MfilterSym0 :: TyFun (a6989586621681401666 ~> Bool) (m6989586621681401665 a6989586621681401666 ~> m6989586621681401665 a6989586621681401666) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad

SuppressUnusedWarnings (FilterMSym0 :: TyFun (a6989586621681401704 ~> m6989586621681401703 Bool) ([a6989586621681401704] ~> m6989586621681401703 [a6989586621681401704]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad

SuppressUnusedWarnings (Let6989586621680320576ZsSym0 :: TyFun (k1 ~> (a6989586621680316340 ~> Bool)) (TyFun k1 (TyFun [a6989586621680316340] [a6989586621680316340] -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680320576YsSym0 :: TyFun (k1 ~> (a6989586621680316340 ~> Bool)) (TyFun k1 (TyFun [a6989586621680316340] [a6989586621680316340] -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680320428NubBy'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_6989586621680320756Sym0 :: TyFun (a6989586621680316437 ~> Bool) (TyFun k (TyFun a6989586621680316437 (TyFun [a6989586621680316437] [a6989586621680316437] -> Type) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680742847Scrutinee_6989586621680742632Sym0 :: TyFun (a6989586621680742384 ~> Bool) (TyFun (t6989586621680742381 a6989586621680742384) Any -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680742834Scrutinee_6989586621680742634Sym0 :: TyFun (a6989586621680742384 ~> Bool) (TyFun (t6989586621680742381 a6989586621680742384) All -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680742749Scrutinee_6989586621680742640Sym0 :: TyFun (a6989586621680742384 ~> Bool) (TyFun (t6989586621680742381 a6989586621680742384) (First a6989586621680742384) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Lambda_6989586621680742750Sym0 :: TyFun (a6989586621679087424 ~> Bool) (TyFun k (TyFun a6989586621679087424 (First a6989586621679087424) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (FindSym0 :: TyFun (a6989586621680742290 ~> Bool) (t6989586621680742289 a6989586621680742290 ~> Maybe a6989586621680742290) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (AnySym0 :: TyFun (a6989586621680742300 ~> Bool) (t6989586621680742299 a6989586621680742300 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (AllSym0 :: TyFun (a6989586621680742298 ~> Bool) (t6989586621680742297 a6989586621680742298 ~> Bool) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Base

(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 (Bool_Sym2 a6989586621679771151 a6989586621679771150 :: TyFun Bool a6989586621679771144 -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Bool

SuppressUnusedWarnings (Elem_bySym2 a6989586621680320413 a6989586621680320412 :: TyFun [a6989586621680316317] Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.Monad

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680320493Scrutinee_6989586621680317017Sym1 n6989586621680320491 :: TyFun k Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Null_6989586621680744215Sym0 :: TyFun (t6989586621680742381 a6989586621680742396) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Null_6989586621680744048Sym0 :: TyFun (t6989586621680742381 a6989586621680742396) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Null_6989586621680743881Sym0 :: TyFun (t6989586621680742381 a6989586621680742396) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Null_6989586621680743732Sym0 :: TyFun (t6989586621680742381 a6989586621680742396) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Null_6989586621680743556Sym0 :: TyFun (t6989586621680742381 a6989586621680742396) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Null_6989586621680743249Sym0 :: TyFun (t6989586621680742381 a6989586621680742396) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (NullSym0 :: TyFun (t6989586621680742381 a6989586621680742396) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (NotElemSym1 a6989586621680742770 t6989586621680742291 :: TyFun (t6989586621680742291 a6989586621680742292) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680744088Sym1 a6989586621680744086 t6989586621680742381 :: TyFun (t6989586621680742381 a6989586621680742398) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680743921Sym1 a6989586621680743919 t6989586621680742381 :: TyFun (t6989586621680742381 a6989586621680742398) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680743754Sym1 a6989586621680743752 t6989586621680742381 :: TyFun (t6989586621680742381 a6989586621680742398) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680743413Sym1 a6989586621680743411 t6989586621680742381 :: TyFun (t6989586621680742381 a6989586621680742398) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Elem_6989586621680743293Sym1 a6989586621680743291 t6989586621680742381 :: TyFun (t6989586621680742381 a6989586621680742398) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (ElemSym1 arg6989586621680743044 t6989586621680742381 :: TyFun (t6989586621680742381 a6989586621680742398) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (AnySym1 a6989586621680742841 t6989586621680742299 :: TyFun (t6989586621680742299 a6989586621680742300) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (AllSym1 a6989586621680742828 t6989586621680742297 :: TyFun (t6989586621680742297 a6989586621680742298) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (TFHelper_6989586621681108278Sym1 a6989586621681108276 :: TyFun (Arg a6989586621681107123 b6989586621681107124) Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Monad

SuppressUnusedWarnings (Lambda_6989586621681401991Sym0 :: TyFun (k1 ~> Bool) (TyFun k (TyFun k1 (m6989586621679962831 k1) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad

SuppressUnusedWarnings (Let6989586621680320760Scrutinee_6989586621680316995Sym1 x6989586621680320758 :: TyFun [a6989586621680316437] (TyFun (k1 ~> Bool) (TyFun k Bool -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.Monad

SuppressUnusedWarnings (Let6989586621680320655Scrutinee_6989586621680317001Sym1 n6989586621680320652 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680320641Scrutinee_6989586621680317003Sym1 n6989586621680320638 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680320474Scrutinee_6989586621680317019Sym1 x6989586621680320471 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Lambda_6989586621680743256Sym1 a_69895866216807432516989586621680743255 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621680320459Scrutinee_6989586621680317021Sym2 xs6989586621680320457 x6989586621680320456 :: TyFun [k1] (TyFun k3 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680320438Scrutinee_6989586621680317023Sym2 ys6989586621680320436 y6989586621680320435 :: TyFun [k1] (TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Lambda_6989586621681402162Sym2 p6989586621681402157 x6989586621681402161 :: TyFun k3 (TyFun Bool (TyFun [k1] [k1] -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad

SuppressUnusedWarnings (Let6989586621680320655Scrutinee_6989586621680317001Sym2 x6989586621680320653 n6989586621680320652 :: TyFun k3 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680320641Scrutinee_6989586621680317003Sym2 x6989586621680320639 n6989586621680320638 :: TyFun k3 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680320561Scrutinee_6989586621680317013Sym2 x6989586621680320558 key6989586621680320557 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680320474Scrutinee_6989586621680317019Sym2 xs6989586621680320472 x6989586621680320471 :: TyFun k3 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Lambda_6989586621680743256Sym2 t6989586621680743263 a_69895866216807432516989586621680743255 :: TyFun k3 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Enum

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

Defined in Data.Singletons.Prelude.Enum

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

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621680320760Scrutinee_6989586621680316995Sym2 xs6989586621680320759 x6989586621680320758 :: TyFun (k1 ~> Bool) (TyFun k Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Lambda_6989586621680320828Sym0 :: TyFun (b6989586621679962835 ~> (a6989586621680316420 ~> Bool)) (TyFun k1 (TyFun k2 (TyFun a6989586621680316420 (TyFun [a6989586621680316420] (TyFun b6989586621679962835 (m6989586621679962831 b6989586621679962835) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Lambda_6989586621681402162Sym3 a_69895866216814021556989586621681402158 p6989586621681402157 x6989586621681402161 :: TyFun Bool (TyFun [k1] [k1] -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad

SuppressUnusedWarnings (Let6989586621680320760Scrutinee_6989586621680316995Sym3 p6989586621680320754 xs6989586621680320759 x6989586621680320758 :: TyFun k Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680320561Scrutinee_6989586621680317013Sym3 y6989586621680320559 x6989586621680320558 key6989586621680320557 :: TyFun k3 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680320459Scrutinee_6989586621680317021Sym3 ls6989586621680320458 xs6989586621680320457 x6989586621680320456 :: TyFun k3 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680129192Scrutinee_6989586621680128958Sym2 x06989586621680129182 x6989586621680129191 :: TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

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

Defined in Data.Singletons.Prelude.Enum

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

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621680320438Scrutinee_6989586621680317023Sym3 xs6989586621680320437 ys6989586621680320436 y6989586621680320435 :: TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680320438Scrutinee_6989586621680317023Sym4 eq6989586621680320426 xs6989586621680320437 ys6989586621680320436 y6989586621680320435 :: TyFun k3 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (Let6989586621680129192Scrutinee_6989586621680128958Sym3 y6989586621680129183 x06989586621680129182 x6989586621680129191 :: TyFun k3 (TyFun k4 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621680129115Scrutinee_6989586621680128972Sym2 x26989586621680129111 x16989586621680129110 :: TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621680129058Scrutinee_6989586621680128982Sym2 x26989586621680129054 x16989586621680129053 :: TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621680129192Scrutinee_6989586621680128958Sym4 arg_69895866216801289546989586621680129178 y6989586621680129183 x06989586621680129182 x6989586621680129191 :: TyFun k4 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621680129115Scrutinee_6989586621680128972Sym3 y6989586621680129112 x26989586621680129111 x16989586621680129110 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621680129058Scrutinee_6989586621680128982Sym3 y6989586621680129055 x26989586621680129054 x16989586621680129053 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621680129115Scrutinee_6989586621680128972Sym4 arg_69895866216801289666989586621680129105 y6989586621680129112 x26989586621680129111 x16989586621680129110 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621680129058Scrutinee_6989586621680128982Sym4 arg_69895866216801289766989586621680129048 y6989586621680129055 x26989586621680129054 x16989586621680129053 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621680129115Scrutinee_6989586621680128972Sym5 arg_69895866216801289686989586621680129106 arg_69895866216801289666989586621680129105 y6989586621680129112 x26989586621680129111 x16989586621680129110 :: TyFun k5 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

SuppressUnusedWarnings (Let6989586621680129058Scrutinee_6989586621680128982Sym5 arg_69895866216801289786989586621680129049 arg_69895866216801289766989586621680129048 y6989586621680129055 x26989586621680129054 x16989586621680129053 :: TyFun k5 Bool -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Rep Bool 
Instance details

Defined in GHC.Generics

type Rep Bool = D1 ('MetaData "Bool" "GHC.Types" "ghc-prim" 'False) (C1 ('MetaCons "False" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "True" 'PrefixI 'False) (U1 :: Type -> Type))
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 Sing 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = SBool
type TypeDocFieldDescriptions Bool 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type ToT Bool 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT Bool = 'TBool
type MaxBound 
Instance details

Defined in Data.Singletons.Prelude.Enum

type MaxBound = MaxBound_6989586621680125214Sym0
type MinBound 
Instance details

Defined in Data.Singletons.Prelude.Enum

type MinBound = MinBound_6989586621680125212Sym0
type Demote Bool 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Show_ (arg0 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Show

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

Defined in Data.Singletons.Prelude.Enum

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

Defined in Data.Singletons.Prelude.Enum

type ToEnum a = Apply ToEnum_6989586621680152573Sym0 a
type Pred (arg0 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Pred (arg0 :: Bool) = Apply (Pred_6989586621680129239Sym0 :: TyFun Bool Bool -> Type) arg0
type Succ (arg0 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Succ (arg0 :: Bool) = Apply (Succ_6989586621680129224Sym0 :: TyFun Bool Bool -> Type) arg0
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_6989586621680577854Sym0 :: 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_6989586621680129249Sym0 :: 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_6989586621679792614Sym0 :: 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_6989586621679792596Sym0 :: 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_6989586621679792578Sym0 :: 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_6989586621679792560Sym0 :: 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_6989586621679792542Sym0 :: 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_6989586621679792524Sym0 :: 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_6989586621679803720Sym0 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_6989586621679776474 a b
type ArithResHs Or Bool Bool Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs And Bool Bool Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Xor Bool Bool Source # 
Instance details

Defined in Lorentz.Arith

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

Defined in Data.Singletons.Prelude.Show

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

Defined in Data.Singletons.Prelude.Bool

type Apply NotSym0 (a6989586621679772458 :: Bool) = Not a6989586621679772458
type Apply FromEnum_6989586621680152586Sym0 (a6989586621680152585 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply FromEnum_6989586621680152586Sym0 (a6989586621680152585 :: Bool) = FromEnum_6989586621680152586 a6989586621680152585
type Apply All_Sym0 (a6989586621680229712 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply All_Sym0 (a6989586621680229712 :: Bool) = All_ a6989586621680229712
type Apply AllSym0 (t6989586621680197047 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply AllSym0 (t6989586621680197047 :: Bool) = 'All t6989586621680197047
type Apply Any_Sym0 (a6989586621680229711 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply Any_Sym0 (a6989586621680229711 :: Bool) = Any_ a6989586621680229711
type Apply AnySym0 (t6989586621680197060 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply AnySym0 (t6989586621680197060 :: Bool) = 'Any t6989586621680197060
type Apply ToEnum_6989586621680152573Sym0 (a6989586621680152572 :: Nat) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply ToEnum_6989586621680152573Sym0 (a6989586621680152572 :: Nat) = ToEnum_6989586621680152573 a6989586621680152572
type Apply GetAllSym0 (a6989586621680197044 :: All) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply GetAllSym0 (a6989586621680197044 :: All) = GetAll a6989586621680197044
type Apply GetAnySym0 (a6989586621680197057 :: Any) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply GetAnySym0 (a6989586621680197057 :: Any) = GetAny a6989586621680197057
type Apply ((||@#@$$) a6989586621679772157 :: TyFun Bool Bool -> Type) (b6989586621679772158 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Bool

type Apply ((||@#@$$) a6989586621679772157 :: TyFun Bool Bool -> Type) (b6989586621679772158 :: Bool) = a6989586621679772157 || b6989586621679772158
type Apply ((&&@#@$$) a6989586621679771912 :: TyFun Bool Bool -> Type) (b6989586621679771913 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Bool

type Apply ((&&@#@$$) a6989586621679771912 :: TyFun Bool Bool -> Type) (b6989586621679771913 :: Bool) = a6989586621679771912 && b6989586621679771913
type Apply (Compare_6989586621679803720Sym1 a6989586621679803718 :: TyFun Bool Ordering -> Type) (a6989586621679803719 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Compare_6989586621679803720Sym1 a6989586621679803718 :: TyFun Bool Ordering -> Type) (a6989586621679803719 :: Bool) = Compare_6989586621679803720 a6989586621679803718 a6989586621679803719
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 (Let6989586621680734291Scrutinee_6989586621680734254Sym1 x6989586621680734284 :: TyFun k1 Bool -> Type) (y6989586621680734285 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680734291Scrutinee_6989586621680734254Sym1 x6989586621680734284 :: TyFun k1 Bool -> Type) (y6989586621680734285 :: k1) = Let6989586621680734291Scrutinee_6989586621680734254 x6989586621680734284 y6989586621680734285
type Apply (Let6989586621680734318Scrutinee_6989586621680734256Sym1 x6989586621680734311 :: TyFun k1 Bool -> Type) (y6989586621680734312 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680734318Scrutinee_6989586621680734256Sym1 x6989586621680734311 :: TyFun k1 Bool -> Type) (y6989586621680734312 :: k1) = Let6989586621680734318Scrutinee_6989586621680734256 x6989586621680734311 y6989586621680734312
type Apply ((==@#@$$) x6989586621679774976 :: TyFun a Bool -> Type) (y6989586621679774977 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Eq

type Apply ((==@#@$$) x6989586621679774976 :: TyFun a Bool -> Type) (y6989586621679774977 :: a) = x6989586621679774976 == y6989586621679774977
type Apply ((/=@#@$$) x6989586621679774978 :: TyFun a Bool -> Type) (y6989586621679774979 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Eq

type Apply ((/=@#@$$) x6989586621679774978 :: TyFun a Bool -> Type) (y6989586621679774979 :: a) = x6989586621679774978 /= y6989586621679774979
type Apply (DefaultEqSym1 a6989586621679774970 :: TyFun k Bool -> Type) (b6989586621679774971 :: k) 
Instance details

Defined in Data.Singletons.Prelude.Eq

type Apply (DefaultEqSym1 a6989586621679774970 :: TyFun k Bool -> Type) (b6989586621679774971 :: k) = DefaultEq a6989586621679774970 b6989586621679774971
type Apply (Let6989586621679792508Scrutinee_6989586621679792399Sym1 x6989586621679792506 :: TyFun k1 Bool -> Type) (y6989586621679792507 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Let6989586621679792508Scrutinee_6989586621679792399Sym1 x6989586621679792506 :: TyFun k1 Bool -> Type) (y6989586621679792507 :: k1) = Let6989586621679792508Scrutinee_6989586621679792399 x6989586621679792506 y6989586621679792507
type Apply (TFHelper_6989586621679792578Sym1 a6989586621679792576 :: TyFun a Bool -> Type) (a6989586621679792577 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (TFHelper_6989586621679792578Sym1 a6989586621679792576 :: TyFun a Bool -> Type) (a6989586621679792577 :: a) = TFHelper_6989586621679792578 a6989586621679792576 a6989586621679792577
type Apply (TFHelper_6989586621679792560Sym1 a6989586621679792558 :: TyFun a Bool -> Type) (a6989586621679792559 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (TFHelper_6989586621679792560Sym1 a6989586621679792558 :: TyFun a Bool -> Type) (a6989586621679792559 :: a) = TFHelper_6989586621679792560 a6989586621679792558 a6989586621679792559
type Apply (TFHelper_6989586621679792542Sym1 a6989586621679792540 :: TyFun a Bool -> Type) (a6989586621679792541 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (TFHelper_6989586621679792542Sym1 a6989586621679792540 :: TyFun a Bool -> Type) (a6989586621679792541 :: a) = TFHelper_6989586621679792542 a6989586621679792540 a6989586621679792541
type Apply (TFHelper_6989586621679792524Sym1 a6989586621679792522 :: TyFun a Bool -> Type) (a6989586621679792523 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (TFHelper_6989586621679792524Sym1 a6989586621679792522 :: TyFun a Bool -> Type) (a6989586621679792523 :: a) = TFHelper_6989586621679792524 a6989586621679792522 a6989586621679792523
type Apply ((<=@#@$$) arg6989586621679792478 :: TyFun a Bool -> Type) (arg6989586621679792479 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply ((<=@#@$$) arg6989586621679792478 :: TyFun a Bool -> Type) (arg6989586621679792479 :: a) = arg6989586621679792478 <= arg6989586621679792479
type Apply ((>=@#@$$) arg6989586621679792486 :: TyFun a Bool -> Type) (arg6989586621679792487 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply ((>=@#@$$) arg6989586621679792486 :: TyFun a Bool -> Type) (arg6989586621679792487 :: a) = arg6989586621679792486 >= arg6989586621679792487
type Apply ((>@#@$$) arg6989586621679792482 :: TyFun a Bool -> Type) (arg6989586621679792483 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply ((>@#@$$) arg6989586621679792482 :: TyFun a Bool -> Type) (arg6989586621679792483 :: a) = arg6989586621679792482 > arg6989586621679792483
type Apply (Let6989586621679792622Scrutinee_6989586621679792413Sym1 x6989586621679792620 :: TyFun k1 Bool -> Type) (y6989586621679792621 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Let6989586621679792622Scrutinee_6989586621679792413Sym1 x6989586621679792620 :: TyFun k1 Bool -> Type) (y6989586621679792621 :: k1) = Let6989586621679792622Scrutinee_6989586621679792413 x6989586621679792620 y6989586621679792621
type Apply (Let6989586621679792604Scrutinee_6989586621679792411Sym1 x6989586621679792602 :: TyFun k1 Bool -> Type) (y6989586621679792603 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Let6989586621679792604Scrutinee_6989586621679792411Sym1 x6989586621679792602 :: TyFun k1 Bool -> Type) (y6989586621679792603 :: k1) = Let6989586621679792604Scrutinee_6989586621679792411 x6989586621679792602 y6989586621679792603
type Apply (Let6989586621679792513Scrutinee_6989586621679792401Sym1 x6989586621679792506 :: TyFun k1 Bool -> Type) (y6989586621679792507 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Let6989586621679792513Scrutinee_6989586621679792401Sym1 x6989586621679792506 :: TyFun k1 Bool -> Type) (y6989586621679792507 :: k1) = Let6989586621679792513Scrutinee_6989586621679792401 x6989586621679792506 y6989586621679792507
type Apply ((<@#@$$) arg6989586621679792474 :: TyFun a Bool -> Type) (arg6989586621679792475 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply ((<@#@$$) arg6989586621679792474 :: TyFun a Bool -> Type) (arg6989586621679792475 :: a) = arg6989586621679792474 < arg6989586621679792475
type Apply (Bool_Sym2 a6989586621679771151 a6989586621679771150 :: TyFun Bool a -> Type) (a6989586621679771152 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Bool

type Apply (Bool_Sym2 a6989586621679771151 a6989586621679771150 :: TyFun Bool a -> Type) (a6989586621679771152 :: Bool) = Bool_ a6989586621679771151 a6989586621679771150 a6989586621679771152
type Apply (Let6989586621680320493Scrutinee_6989586621680317017Sym1 n6989586621680320491 :: TyFun k Bool -> Type) (x6989586621680320492 :: k) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680320493Scrutinee_6989586621680317017Sym1 n6989586621680320491 :: TyFun k Bool -> Type) (x6989586621680320492 :: k) = Let6989586621680320493Scrutinee_6989586621680317017 n6989586621680320491 x6989586621680320492
type Apply (Let6989586621680320474Scrutinee_6989586621680317019Sym2 xs6989586621680320472 x6989586621680320471 :: TyFun k3 Bool -> Type) (n6989586621680320473 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680320474Scrutinee_6989586621680317019Sym2 xs6989586621680320472 x6989586621680320471 :: TyFun k3 Bool -> Type) (n6989586621680320473 :: k3) = Let6989586621680320474Scrutinee_6989586621680317019 xs6989586621680320472 x6989586621680320471 n6989586621680320473
type Apply (Let6989586621680320641Scrutinee_6989586621680317003Sym2 x6989586621680320639 n6989586621680320638 :: TyFun k3 Bool -> Type) (xs6989586621680320640 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680320641Scrutinee_6989586621680317003Sym2 x6989586621680320639 n6989586621680320638 :: TyFun k3 Bool -> Type) (xs6989586621680320640 :: k3) = Let6989586621680320641Scrutinee_6989586621680317003 x6989586621680320639 n6989586621680320638 xs6989586621680320640
type Apply (Let6989586621680320655Scrutinee_6989586621680317001Sym2 x6989586621680320653 n6989586621680320652 :: TyFun k3 Bool -> Type) (xs6989586621680320654 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680320655Scrutinee_6989586621680317001Sym2 x6989586621680320653 n6989586621680320652 :: TyFun k3 Bool -> Type) (xs6989586621680320654 :: k3) = Let6989586621680320655Scrutinee_6989586621680317001 x6989586621680320653 n6989586621680320652 xs6989586621680320654
type Apply (Lambda_6989586621680743256Sym2 t6989586621680743263 a_69895866216807432516989586621680743255 :: TyFun k3 Bool -> Type) (t6989586621680743264 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Lambda_6989586621680743256Sym2 t6989586621680743263 a_69895866216807432516989586621680743255 :: TyFun k3 Bool -> Type) (t6989586621680743264 :: k3) = Lambda_6989586621680743256 t6989586621680743263 a_69895866216807432516989586621680743255 t6989586621680743264
type Apply (Let6989586621680320561Scrutinee_6989586621680317013Sym3 y6989586621680320559 x6989586621680320558 key6989586621680320557 :: TyFun k3 Bool -> Type) (xys6989586621680320560 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680320561Scrutinee_6989586621680317013Sym3 y6989586621680320559 x6989586621680320558 key6989586621680320557 :: TyFun k3 Bool -> Type) (xys6989586621680320560 :: k3) = Let6989586621680320561Scrutinee_6989586621680317013 y6989586621680320559 x6989586621680320558 key6989586621680320557 xys6989586621680320560
type Apply (Let6989586621680320459Scrutinee_6989586621680317021Sym3 ls6989586621680320458 xs6989586621680320457 x6989586621680320456 :: TyFun k3 Bool -> Type) (l6989586621680320449 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680320459Scrutinee_6989586621680317021Sym3 ls6989586621680320458 xs6989586621680320457 x6989586621680320456 :: TyFun k3 Bool -> Type) (l6989586621680320449 :: k3) = Let6989586621680320459Scrutinee_6989586621680317021 ls6989586621680320458 xs6989586621680320457 x6989586621680320456 l6989586621680320449
type Apply (Let6989586621680320760Scrutinee_6989586621680316995Sym3 p6989586621680320754 xs6989586621680320759 x6989586621680320758 :: TyFun k Bool -> Type) (a_69895866216803207526989586621680320755 :: k) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680320760Scrutinee_6989586621680316995Sym3 p6989586621680320754 xs6989586621680320759 x6989586621680320758 :: TyFun k Bool -> Type) (a_69895866216803207526989586621680320755 :: k) = Let6989586621680320760Scrutinee_6989586621680316995 p6989586621680320754 xs6989586621680320759 x6989586621680320758 a_69895866216803207526989586621680320755
type Apply (Let6989586621680320438Scrutinee_6989586621680317023Sym4 eq6989586621680320426 xs6989586621680320437 ys6989586621680320436 y6989586621680320435 :: TyFun k3 Bool -> Type) (l6989586621680320427 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680320438Scrutinee_6989586621680317023Sym4 eq6989586621680320426 xs6989586621680320437 ys6989586621680320436 y6989586621680320435 :: TyFun k3 Bool -> Type) (l6989586621680320427 :: k3) = Let6989586621680320438Scrutinee_6989586621680317023 eq6989586621680320426 xs6989586621680320437 ys6989586621680320436 y6989586621680320435 l6989586621680320427
type Apply (Let6989586621680129192Scrutinee_6989586621680128958Sym4 arg_69895866216801289546989586621680129178 y6989586621680129183 x06989586621680129182 x6989586621680129191 :: TyFun k4 Bool -> Type) (arg_69895866216801289566989586621680129179 :: k4) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621680129192Scrutinee_6989586621680128958Sym4 arg_69895866216801289546989586621680129178 y6989586621680129183 x06989586621680129182 x6989586621680129191 :: TyFun k4 Bool -> Type) (arg_69895866216801289566989586621680129179 :: k4) = Let6989586621680129192Scrutinee_6989586621680128958 arg_69895866216801289546989586621680129178 y6989586621680129183 x06989586621680129182 x6989586621680129191 arg_69895866216801289566989586621680129179
type Apply (Let6989586621680129058Scrutinee_6989586621680128982Sym5 arg_69895866216801289786989586621680129049 arg_69895866216801289766989586621680129048 y6989586621680129055 x26989586621680129054 x16989586621680129053 :: TyFun k5 Bool -> Type) (arg_69895866216801289806989586621680129050 :: k5) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621680129058Scrutinee_6989586621680128982Sym5 arg_69895866216801289786989586621680129049 arg_69895866216801289766989586621680129048 y6989586621680129055 x26989586621680129054 x16989586621680129053 :: TyFun k5 Bool -> Type) (arg_69895866216801289806989586621680129050 :: k5) = Let6989586621680129058Scrutinee_6989586621680128982 arg_69895866216801289786989586621680129049 arg_69895866216801289766989586621680129048 y6989586621680129055 x26989586621680129054 x16989586621680129053 arg_69895866216801289806989586621680129050
type Apply (Let6989586621680129115Scrutinee_6989586621680128972Sym5 arg_69895866216801289686989586621680129106 arg_69895866216801289666989586621680129105 y6989586621680129112 x26989586621680129111 x16989586621680129110 :: TyFun k5 Bool -> Type) (arg_69895866216801289706989586621680129107 :: k5) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621680129115Scrutinee_6989586621680128972Sym5 arg_69895866216801289686989586621680129106 arg_69895866216801289666989586621680129105 y6989586621680129112 x26989586621680129111 x16989586621680129110 :: TyFun k5 Bool -> Type) (arg_69895866216801289706989586621680129107 :: k5) = Let6989586621680129115Scrutinee_6989586621680128972 arg_69895866216801289686989586621680129106 arg_69895866216801289666989586621680129105 y6989586621680129112 x26989586621680129111 x16989586621680129110 arg_69895866216801289706989586621680129107
type Eval (Not 'False) 
Instance details

Defined in Fcf.Data.Bool

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

Defined in Fcf.Data.Bool

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

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (GuardSym0 :: TyFun Bool (f6989586621679962724 ()) -> Type) (a6989586621679962890 :: Bool) = Guard a6989586621679962890 :: f6989586621679962724 ()
type Eval (Null (a2 ': as) :: Bool -> Type) 
Instance details

Defined in Fcf.Data.List

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

Defined in Fcf.Data.List

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

Defined in Fcf.Data.Nat

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

Defined in Fcf.Data.Nat

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

Defined in Fcf.Data.Nat

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

Defined in Fcf.Data.Nat

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

Defined in Fcf.Data.Bool

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

Defined in Fcf.Data.Bool

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

Defined in Fcf.Data.Bool

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

Defined in Fcf.Data.Bool

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

Defined in Fcf.Data.Bool

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

Defined in Fcf.Data.Bool

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

Defined in Fcf.Data.Bool

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

Defined in Fcf.Data.Bool

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

Defined in Fcf.Data.Common

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

Defined in Fcf.Data.Common

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

Defined in Fcf.Data.Common

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

Defined in Fcf.Data.Common

type Eval (IsJust ('Just _a) :: Bool -> Type) = 'True
type Apply (||@#@$) (a6989586621679772157 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Bool

type Apply (||@#@$) (a6989586621679772157 :: Bool) = (||@#@$$) a6989586621679772157
type Apply (&&@#@$) (a6989586621679771912 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Bool

type Apply (&&@#@$) (a6989586621679771912 :: Bool) = (&&@#@$$) a6989586621679771912
type Apply Compare_6989586621679803720Sym0 (a6989586621679803718 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply Compare_6989586621679803720Sym0 (a6989586621679803718 :: Bool) = Compare_6989586621679803720Sym1 a6989586621679803718
type Apply ShowParenSym0 (a6989586621680577755 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply ShowParenSym0 (a6989586621680577755 :: Bool) = ShowParenSym1 a6989586621680577755
type Apply ShowsPrec_6989586621680595859Sym0 (a6989586621680595856 :: Nat) 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply ShowsPrec_6989586621680595859Sym0 (a6989586621680595856 :: Nat) = ShowsPrec_6989586621680595859Sym1 a6989586621680595856
type Apply (<=?@#@$) (a3530822107858468865 :: Nat) 
Instance details

Defined in Data.Singletons.TypeLits.Internal

type Apply (<=?@#@$) (a3530822107858468865 :: Nat) = (<=?@#@$$) a3530822107858468865
type Apply (ShowsPrec_6989586621680595859Sym1 a6989586621680595856 :: TyFun Bool (Symbol ~> Symbol) -> Type) (a6989586621680595857 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowsPrec_6989586621680595859Sym1 a6989586621680595856 :: TyFun Bool (Symbol ~> Symbol) -> Type) (a6989586621680595857 :: Bool) = ShowsPrec_6989586621680595859Sym2 a6989586621680595856 a6989586621680595857
type Apply (UnlessSym0 :: TyFun Bool (f6989586621681401670 () ~> f6989586621681401670 ()) -> Type) (a6989586621681402022 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Monad

type Apply (UnlessSym0 :: TyFun Bool (f6989586621681401670 () ~> f6989586621681401670 ()) -> Type) (a6989586621681402022 :: Bool) = UnlessSym1 a6989586621681402022 f6989586621681401670 :: TyFun (f6989586621681401670 ()) (f6989586621681401670 ()) -> Type
type Apply (WhenSym0 :: TyFun Bool (f6989586621679962753 () ~> f6989586621679962753 ()) -> Type) (a6989586621679963138 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (WhenSym0 :: TyFun Bool (f6989586621679962753 () ~> f6989586621679962753 ()) -> Type) (a6989586621679963138 :: Bool) = WhenSym1 a6989586621679963138 f6989586621679962753 :: TyFun (f6989586621679962753 ()) (f6989586621679962753 ()) -> Type
type Apply (ListelemSym0 :: TyFun a6989586621680686793 ([a6989586621680686793] ~> Bool) -> Type) (a6989586621680687700 :: a6989586621680686793) 
Instance details

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

type Apply (ListelemSym0 :: TyFun a6989586621680686793 ([a6989586621680686793] ~> Bool) -> Type) (a6989586621680687700 :: a6989586621680686793) = ListelemSym1 a6989586621680687700
type Apply (NotElemSym0 :: TyFun a6989586621680316399 ([a6989586621680316399] ~> Bool) -> Type) (a6989586621680321269 :: a6989586621680316399) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (NotElemSym0 :: TyFun a6989586621680316399 ([a6989586621680316399] ~> Bool) -> Type) (a6989586621680321269 :: a6989586621680316399) = NotElemSym1 a6989586621680321269
type Apply (ElemSym0 :: TyFun a6989586621680316400 ([a6989586621680316400] ~> Bool) -> Type) (a6989586621680321276 :: a6989586621680316400) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ElemSym0 :: TyFun a6989586621680316400 ([a6989586621680316400] ~> Bool) -> Type) (a6989586621680321276 :: a6989586621680316400) = ElemSym1 a6989586621680321276
type Apply (Let6989586621680734291Scrutinee_6989586621680734254Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621680734284 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680734291Scrutinee_6989586621680734254Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621680734284 :: k1) = Let6989586621680734291Scrutinee_6989586621680734254Sym1 x6989586621680734284
type Apply (Let6989586621680734318Scrutinee_6989586621680734256Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621680734311 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680734318Scrutinee_6989586621680734256Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621680734311 :: k1) = Let6989586621680734318Scrutinee_6989586621680734256Sym1 x6989586621680734311
type Apply ((==@#@$) :: TyFun a6989586621679774975 (a6989586621679774975 ~> Bool) -> Type) (x6989586621679774976 :: a6989586621679774975) 
Instance details

Defined in Data.Singletons.Prelude.Eq

type Apply ((==@#@$) :: TyFun a6989586621679774975 (a6989586621679774975 ~> Bool) -> Type) (x6989586621679774976 :: a6989586621679774975) = (==@#@$$) x6989586621679774976
type Apply ((/=@#@$) :: TyFun a6989586621679774975 (a6989586621679774975 ~> Bool) -> Type) (x6989586621679774978 :: a6989586621679774975) 
Instance details

Defined in Data.Singletons.Prelude.Eq

type Apply ((/=@#@$) :: TyFun a6989586621679774975 (a6989586621679774975 ~> Bool) -> Type) (x6989586621679774978 :: a6989586621679774975) = (/=@#@$$) x6989586621679774978
type Apply (DefaultEqSym0 :: TyFun k6989586621679774969 (k6989586621679774969 ~> Bool) -> Type) (a6989586621679774970 :: k6989586621679774969) 
Instance details

Defined in Data.Singletons.Prelude.Eq

type Apply (DefaultEqSym0 :: TyFun k6989586621679774969 (k6989586621679774969 ~> Bool) -> Type) (a6989586621679774970 :: k6989586621679774969) = DefaultEqSym1 a6989586621679774970
type Apply (Bool_Sym0 :: TyFun a6989586621679771144 (a6989586621679771144 ~> (Bool ~> a6989586621679771144)) -> Type) (a6989586621679771150 :: a6989586621679771144) 
Instance details

Defined in Data.Singletons.Prelude.Bool

type Apply (Bool_Sym0 :: TyFun a6989586621679771144 (a6989586621679771144 ~> (Bool ~> a6989586621679771144)) -> Type) (a6989586621679771150 :: a6989586621679771144) = Bool_Sym1 a6989586621679771150
type Apply (Let6989586621679792508Scrutinee_6989586621679792399Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679792506 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Let6989586621679792508Scrutinee_6989586621679792399Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679792506 :: k1) = Let6989586621679792508Scrutinee_6989586621679792399Sym1 x6989586621679792506
type Apply (TFHelper_6989586621679792578Sym0 :: TyFun a6989586621679792381 (a6989586621679792381 ~> Bool) -> Type) (a6989586621679792576 :: a6989586621679792381) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (TFHelper_6989586621679792578Sym0 :: TyFun a6989586621679792381 (a6989586621679792381 ~> Bool) -> Type) (a6989586621679792576 :: a6989586621679792381) = TFHelper_6989586621679792578Sym1 a6989586621679792576
type Apply (TFHelper_6989586621679792560Sym0 :: TyFun a6989586621679792381 (a6989586621679792381 ~> Bool) -> Type) (a6989586621679792558 :: a6989586621679792381) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (TFHelper_6989586621679792560Sym0 :: TyFun a6989586621679792381 (a6989586621679792381 ~> Bool) -> Type) (a6989586621679792558 :: a6989586621679792381) = TFHelper_6989586621679792560Sym1 a6989586621679792558
type Apply (TFHelper_6989586621679792542Sym0 :: TyFun a6989586621679792381 (a6989586621679792381 ~> Bool) -> Type) (a6989586621679792540 :: a6989586621679792381) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (TFHelper_6989586621679792542Sym0 :: TyFun a6989586621679792381 (a6989586621679792381 ~> Bool) -> Type) (a6989586621679792540 :: a6989586621679792381) = TFHelper_6989586621679792542Sym1 a6989586621679792540
type Apply (TFHelper_6989586621679792524Sym0 :: TyFun a6989586621679792381 (a6989586621679792381 ~> Bool) -> Type) (a6989586621679792522 :: a6989586621679792381) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (TFHelper_6989586621679792524Sym0 :: TyFun a6989586621679792381 (a6989586621679792381 ~> Bool) -> Type) (a6989586621679792522 :: a6989586621679792381) = TFHelper_6989586621679792524Sym1 a6989586621679792522
type Apply ((<=@#@$) :: TyFun a6989586621679792381 (a6989586621679792381 ~> Bool) -> Type) (arg6989586621679792478 :: a6989586621679792381) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply ((<=@#@$) :: TyFun a6989586621679792381 (a6989586621679792381 ~> Bool) -> Type) (arg6989586621679792478 :: a6989586621679792381) = (<=@#@$$) arg6989586621679792478
type Apply ((>=@#@$) :: TyFun a6989586621679792381 (a6989586621679792381 ~> Bool) -> Type) (arg6989586621679792486 :: a6989586621679792381) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply ((>=@#@$) :: TyFun a6989586621679792381 (a6989586621679792381 ~> Bool) -> Type) (arg6989586621679792486 :: a6989586621679792381) = (>=@#@$$) arg6989586621679792486
type Apply ((>@#@$) :: TyFun a6989586621679792381 (a6989586621679792381 ~> Bool) -> Type) (arg6989586621679792482 :: a6989586621679792381) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply ((>@#@$) :: TyFun a6989586621679792381 (a6989586621679792381 ~> Bool) -> Type) (arg6989586621679792482 :: a6989586621679792381) = (>@#@$$) arg6989586621679792482
type Apply (Let6989586621679792622Scrutinee_6989586621679792413Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679792620 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Let6989586621679792622Scrutinee_6989586621679792413Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679792620 :: k1) = Let6989586621679792622Scrutinee_6989586621679792413Sym1 x6989586621679792620
type Apply (Let6989586621679792604Scrutinee_6989586621679792411Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679792602 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Let6989586621679792604Scrutinee_6989586621679792411Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679792602 :: k1) = Let6989586621679792604Scrutinee_6989586621679792411Sym1 x6989586621679792602
type Apply (Let6989586621679792513Scrutinee_6989586621679792401Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679792506 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Let6989586621679792513Scrutinee_6989586621679792401Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679792506 :: k1) = Let6989586621679792513Scrutinee_6989586621679792401Sym1 x6989586621679792506
type Apply ((<@#@$) :: TyFun a6989586621679792381 (a6989586621679792381 ~> Bool) -> Type) (arg6989586621679792474 :: a6989586621679792381) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply ((<@#@$) :: TyFun a6989586621679792381 (a6989586621679792381 ~> Bool) -> Type) (arg6989586621679792474 :: a6989586621679792381) = (<@#@$$) arg6989586621679792474
type Apply (Elem_6989586621680921217Sym0 :: TyFun a6989586621680742398 (Identity a6989586621680742398 ~> Bool) -> Type) (a6989586621680921215 :: a6989586621680742398) 
Instance details

Defined in Data.Singletons.Prelude.Identity

type Apply (Elem_6989586621680921217Sym0 :: TyFun a6989586621680742398 (Identity a6989586621680742398 ~> Bool) -> Type) (a6989586621680921215 :: a6989586621680742398) = Elem_6989586621680921217Sym1 a6989586621680921215
type Apply (Let6989586621680320493Scrutinee_6989586621680317017Sym0 :: TyFun k1 (TyFun k Bool -> Type) -> Type) (n6989586621680320491 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680320493Scrutinee_6989586621680317017Sym0 :: TyFun k1 (TyFun k Bool -> Type) -> Type) (n6989586621680320491 :: k1) = Let6989586621680320493Scrutinee_6989586621680317017Sym1 n6989586621680320491 :: TyFun k Bool -> Type
type Apply (Elem_bySym1 a6989586621680320412 :: TyFun a6989586621680316317 ([a6989586621680316317] ~> Bool) -> Type) (a6989586621680320413 :: a6989586621680316317) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Elem_bySym1 a6989586621680320412 :: TyFun a6989586621680316317 ([a6989586621680316317] ~> Bool) -> Type) (a6989586621680320413 :: a6989586621680316317) = Elem_bySym2 a6989586621680320412 a6989586621680320413
type Apply (Elem_6989586621680743293Sym0 :: TyFun a6989586621680742398 (t6989586621680742381 a6989586621680742398 ~> Bool) -> Type) (a6989586621680743291 :: a6989586621680742398) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680743293Sym0 :: TyFun a6989586621680742398 (t6989586621680742381 a6989586621680742398 ~> Bool) -> Type) (a6989586621680743291 :: a6989586621680742398) = Elem_6989586621680743293Sym1 a6989586621680743291 t6989586621680742381 :: TyFun (t6989586621680742381 a6989586621680742398) Bool -> Type
type Apply (ElemSym0 :: TyFun a6989586621680742398 (t6989586621680742381 a6989586621680742398 ~> Bool) -> Type) (arg6989586621680743044 :: a6989586621680742398) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ElemSym0 :: TyFun a6989586621680742398 (t6989586621680742381 a6989586621680742398 ~> Bool) -> Type) (arg6989586621680743044 :: a6989586621680742398) = ElemSym1 arg6989586621680743044 t6989586621680742381 :: TyFun (t6989586621680742381 a6989586621680742398) Bool -> Type
type Apply (NotElemSym0 :: TyFun a6989586621680742292 (t6989586621680742291 a6989586621680742292 ~> Bool) -> Type) (a6989586621680742770 :: a6989586621680742292) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (NotElemSym0 :: TyFun a6989586621680742292 (t6989586621680742291 a6989586621680742292 ~> Bool) -> Type) (a6989586621680742770 :: a6989586621680742292) = NotElemSym1 a6989586621680742770 t6989586621680742291 :: TyFun (t6989586621680742291 a6989586621680742292) Bool -> Type
type Apply (Elem_6989586621680743413Sym0 :: TyFun a6989586621680742398 (t6989586621680742381 a6989586621680742398 ~> Bool) -> Type) (a6989586621680743411 :: a6989586621680742398) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680743413Sym0 :: TyFun a6989586621680742398 (t6989586621680742381 a6989586621680742398 ~> Bool) -> Type) (a6989586621680743411 :: a6989586621680742398) = Elem_6989586621680743413Sym1 a6989586621680743411 t6989586621680742381 :: TyFun (t6989586621680742381 a6989586621680742398) Bool -> Type
type Apply (Elem_6989586621680743754Sym0 :: TyFun a6989586621680742398 (t6989586621680742381 a6989586621680742398 ~> Bool) -> Type) (a6989586621680743752 :: a6989586621680742398) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680743754Sym0 :: TyFun a6989586621680742398 (t6989586621680742381 a6989586621680742398 ~> Bool) -> Type) (a6989586621680743752 :: a6989586621680742398) = Elem_6989586621680743754Sym1 a6989586621680743752 t6989586621680742381 :: TyFun (t6989586621680742381 a6989586621680742398) Bool -> Type
type Apply (Elem_6989586621680743921Sym0 :: TyFun a6989586621680742398 (t6989586621680742381 a6989586621680742398 ~> Bool) -> Type) (a6989586621680743919 :: a6989586621680742398) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680743921Sym0 :: TyFun a6989586621680742398 (t6989586621680742381 a6989586621680742398 ~> Bool) -> Type) (a6989586621680743919 :: a6989586621680742398) = Elem_6989586621680743921Sym1 a6989586621680743919 t6989586621680742381 :: TyFun (t6989586621680742381 a6989586621680742398) Bool -> Type
type Apply (Elem_6989586621680744088Sym0 :: TyFun a6989586621680742398 (t6989586621680742381 a6989586621680742398 ~> Bool) -> Type) (a6989586621680744086 :: a6989586621680742398) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680744088Sym0 :: TyFun a6989586621680742398 (t6989586621680742381 a6989586621680742398 ~> Bool) -> Type) (a6989586621680744086 :: a6989586621680742398) = Elem_6989586621680744088Sym1 a6989586621680744086 t6989586621680742381 :: TyFun (t6989586621680742381 a6989586621680742398) Bool -> Type
type Apply (Bool_Sym1 a6989586621679771150 :: TyFun a6989586621679771144 (Bool ~> a6989586621679771144) -> Type) (a6989586621679771151 :: a6989586621679771144) 
Instance details

Defined in Data.Singletons.Prelude.Bool

type Apply (Bool_Sym1 a6989586621679771150 :: TyFun a6989586621679771144 (Bool ~> a6989586621679771144) -> Type) (a6989586621679771151 :: a6989586621679771144) = Bool_Sym2 a6989586621679771150 a6989586621679771151
type Apply (Lambda_6989586621681402162Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun Bool (TyFun [k1] [k1] -> Type) -> Type) -> Type) -> Type) -> Type) (x6989586621681402161 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Monad

type Apply (Lambda_6989586621681402162Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun Bool (TyFun [k1] [k1] -> Type) -> Type) -> Type) -> Type) -> Type) (x6989586621681402161 :: k1) = Lambda_6989586621681402162Sym1 x6989586621681402161 :: TyFun k2 (TyFun k3 (TyFun Bool (TyFun [k1] [k1] -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621680320474Scrutinee_6989586621680317019Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (x6989586621680320471 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680320474Scrutinee_6989586621680317019Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (x6989586621680320471 :: k1) = Let6989586621680320474Scrutinee_6989586621680317019Sym1 x6989586621680320471 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type
type Apply (Let6989586621680320561Scrutinee_6989586621680317013Sym0 :: TyFun k1 (TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) (key6989586621680320557 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680320561Scrutinee_6989586621680317013Sym0 :: TyFun k1 (TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) (key6989586621680320557 :: k1) = Let6989586621680320561Scrutinee_6989586621680317013Sym1 key6989586621680320557 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type
type Apply (Let6989586621680320641Scrutinee_6989586621680317003Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (n6989586621680320638 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680320641Scrutinee_6989586621680317003Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (n6989586621680320638 :: k1) = Let6989586621680320641Scrutinee_6989586621680317003Sym1 n6989586621680320638 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type
type Apply (Let6989586621680320655Scrutinee_6989586621680317001Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (n6989586621680320652 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680320655Scrutinee_6989586621680317001Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (n6989586621680320652 :: k1) = Let6989586621680320655Scrutinee_6989586621680317001Sym1 n6989586621680320652 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type
type Apply (Let6989586621680320438Scrutinee_6989586621680317023Sym0 :: TyFun k1 (TyFun k2 (TyFun [k1] (TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (y6989586621680320435 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680320438Scrutinee_6989586621680317023Sym0 :: TyFun k1 (TyFun k2 (TyFun [k1] (TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (y6989586621680320435 :: k1) = Let6989586621680320438Scrutinee_6989586621680317023Sym1 y6989586621680320435 :: TyFun k2 (TyFun [k1] (TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621680320459Scrutinee_6989586621680317021Sym0 :: TyFun k1 (TyFun k2 (TyFun [k1] (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) (x6989586621680320456 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680320459Scrutinee_6989586621680317021Sym0 :: TyFun k1 (TyFun k2 (TyFun [k1] (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) (x6989586621680320456 :: k1) = Let6989586621680320459Scrutinee_6989586621680317021Sym1 x6989586621680320456 :: TyFun k2 (TyFun [k1] (TyFun k3 Bool -> Type) -> Type) -> Type
type Apply (Let6989586621680320760Scrutinee_6989586621680316995Sym0 :: TyFun k1 (TyFun [a6989586621680316437] (TyFun (k1 ~> Bool) (TyFun k Bool -> Type) -> Type) -> Type) -> Type) (x6989586621680320758 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680320760Scrutinee_6989586621680316995Sym0 :: TyFun k1 (TyFun [a6989586621680316437] (TyFun (k1 ~> Bool) (TyFun k Bool -> Type) -> Type) -> Type) -> Type) (x6989586621680320758 :: k1) = Let6989586621680320760Scrutinee_6989586621680316995Sym1 x6989586621680320758 :: TyFun [a6989586621680316437] (TyFun (k1 ~> Bool) (TyFun k Bool -> Type) -> Type) -> Type
type Apply (Lambda_6989586621680743256Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (a_69895866216807432516989586621680743255 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Lambda_6989586621680743256Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (a_69895866216807432516989586621680743255 :: k1) = Lambda_6989586621680743256Sym1 a_69895866216807432516989586621680743255 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type
type Apply (Lambda_6989586621681402162Sym1 x6989586621681402161 :: TyFun k2 (TyFun k3 (TyFun Bool (TyFun [k1] [k1] -> Type) -> Type) -> Type) -> Type) (p6989586621681402157 :: k2) 
Instance details

Defined in Data.Singletons.Prelude.Monad

type Apply (Lambda_6989586621681402162Sym1 x6989586621681402161 :: TyFun k2 (TyFun k3 (TyFun Bool (TyFun [k1] [k1] -> Type) -> Type) -> Type) -> Type) (p6989586621681402157 :: k2) = Lambda_6989586621681402162Sym2 x6989586621681402161 p6989586621681402157 :: TyFun k3 (TyFun Bool (TyFun [k1] [k1] -> Type) -> Type) -> Type
type Apply (Let6989586621680320474Scrutinee_6989586621680317019Sym1 x6989586621680320471 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) (xs6989586621680320472 :: k2) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680320474Scrutinee_6989586621680317019Sym1 x6989586621680320471 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) (xs6989586621680320472 :: k2) = Let6989586621680320474Scrutinee_6989586621680317019Sym2 x6989586621680320471 xs6989586621680320472 :: TyFun k3 Bool -> Type
type Apply (Let6989586621680320561Scrutinee_6989586621680317013Sym1 key6989586621680320557 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (x6989586621680320558 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680320561Scrutinee_6989586621680317013Sym1 key6989586621680320557 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (x6989586621680320558 :: k1) = Let6989586621680320561Scrutinee_6989586621680317013Sym2 key6989586621680320557 x6989586621680320558 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type
type Apply (Let6989586621680320641Scrutinee_6989586621680317003Sym1 n6989586621680320638 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) (x6989586621680320639 :: k2) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680320641Scrutinee_6989586621680317003Sym1 n6989586621680320638 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) (x6989586621680320639 :: k2) = Let6989586621680320641Scrutinee_6989586621680317003Sym2 n6989586621680320638 x6989586621680320639 :: TyFun k3 Bool -> Type
type Apply (Let6989586621680320655Scrutinee_6989586621680317001Sym1 n6989586621680320652 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) (x6989586621680320653 :: k2) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680320655Scrutinee_6989586621680317001Sym1 n6989586621680320652 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) (x6989586621680320653 :: k2) = Let6989586621680320655Scrutinee_6989586621680317001Sym2 n6989586621680320652 x6989586621680320653 :: TyFun k3 Bool -> Type
type Apply (Let6989586621680320438Scrutinee_6989586621680317023Sym1 y6989586621680320435 :: TyFun k2 (TyFun [k1] (TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) (ys6989586621680320436 :: k2) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680320438Scrutinee_6989586621680317023Sym1 y6989586621680320435 :: TyFun k2 (TyFun [k1] (TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) (ys6989586621680320436 :: k2) = Let6989586621680320438Scrutinee_6989586621680317023Sym2 y6989586621680320435 ys6989586621680320436 :: TyFun [k1] (TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type) -> Type
type Apply (Let6989586621680320459Scrutinee_6989586621680317021Sym1 x6989586621680320456 :: TyFun k2 (TyFun [k1] (TyFun k3 Bool -> Type) -> Type) -> Type) (xs6989586621680320457 :: k2) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680320459Scrutinee_6989586621680317021Sym1 x6989586621680320456 :: TyFun k2 (TyFun [k1] (TyFun k3 Bool -> Type) -> Type) -> Type) (xs6989586621680320457 :: k2) = Let6989586621680320459Scrutinee_6989586621680317021Sym2 x6989586621680320456 xs6989586621680320457 :: TyFun [k1] (TyFun k3 Bool -> Type) -> Type
type Apply (Lambda_6989586621680743256Sym1 a_69895866216807432516989586621680743255 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) (t6989586621680743263 :: k2) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Lambda_6989586621680743256Sym1 a_69895866216807432516989586621680743255 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) (t6989586621680743263 :: k2) = Lambda_6989586621680743256Sym2 a_69895866216807432516989586621680743255 t6989586621680743263 :: TyFun k3 Bool -> Type
type Apply (Let6989586621680129192Scrutinee_6989586621680128958Sym0 :: TyFun k1 (TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (x6989586621680129191 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621680129192Scrutinee_6989586621680128958Sym0 :: TyFun k1 (TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (x6989586621680129191 :: k1) = Let6989586621680129192Scrutinee_6989586621680128958Sym1 x6989586621680129191 :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621681402162Sym2 p6989586621681402157 x6989586621681402161 :: TyFun k3 (TyFun Bool (TyFun [k1] [k1] -> Type) -> Type) -> Type) (a_69895866216814021556989586621681402158 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.Monad

type Apply (Lambda_6989586621681402162Sym2 p6989586621681402157 x6989586621681402161 :: TyFun k3 (TyFun Bool (TyFun [k1] [k1] -> Type) -> Type) -> Type) (a_69895866216814021556989586621681402158 :: k3) = Lambda_6989586621681402162Sym3 p6989586621681402157 x6989586621681402161 a_69895866216814021556989586621681402158
type Apply (Let6989586621680320561Scrutinee_6989586621680317013Sym2 x6989586621680320558 key6989586621680320557 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) (y6989586621680320559 :: k2) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680320561Scrutinee_6989586621680317013Sym2 x6989586621680320558 key6989586621680320557 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) (y6989586621680320559 :: k2) = Let6989586621680320561Scrutinee_6989586621680317013Sym3 x6989586621680320558 key6989586621680320557 y6989586621680320559 :: TyFun k3 Bool -> Type
type Apply (Let6989586621680129058Scrutinee_6989586621680128982Sym0 :: TyFun k1 (TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (x16989586621680129053 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621680129058Scrutinee_6989586621680128982Sym0 :: TyFun k1 (TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (x16989586621680129053 :: k1) = Let6989586621680129058Scrutinee_6989586621680128982Sym1 x16989586621680129053 :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621680129115Scrutinee_6989586621680128972Sym0 :: TyFun k1 (TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (x16989586621680129110 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621680129115Scrutinee_6989586621680128972Sym0 :: TyFun k1 (TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (x16989586621680129110 :: k1) = Let6989586621680129115Scrutinee_6989586621680128972Sym1 x16989586621680129110 :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621680129192Scrutinee_6989586621680128958Sym1 x6989586621680129191 :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) (x06989586621680129182 :: k2) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621680129192Scrutinee_6989586621680128958Sym1 x6989586621680129191 :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) (x06989586621680129182 :: k2) = Let6989586621680129192Scrutinee_6989586621680128958Sym2 x6989586621680129191 x06989586621680129182 :: TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type
type Apply (Lambda_6989586621681402162Sym3 a_69895866216814021556989586621681402158 p6989586621681402157 x6989586621681402161 :: TyFun Bool (TyFun [k1] [k1] -> Type) -> Type) (t6989586621681402168 :: Bool) 
Instance details

Defined in Data.Singletons.Prelude.Monad

type Apply (Lambda_6989586621681402162Sym3 a_69895866216814021556989586621681402158 p6989586621681402157 x6989586621681402161 :: TyFun Bool (TyFun [k1] [k1] -> Type) -> Type) (t6989586621681402168 :: Bool) = Lambda_6989586621681402162 a_69895866216814021556989586621681402158 p6989586621681402157 x6989586621681402161 t6989586621681402168
type Apply (Let6989586621680129058Scrutinee_6989586621680128982Sym1 x16989586621680129053 :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (x26989586621680129054 :: k2) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621680129058Scrutinee_6989586621680128982Sym1 x16989586621680129053 :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (x26989586621680129054 :: k2) = Let6989586621680129058Scrutinee_6989586621680128982Sym2 x16989586621680129053 x26989586621680129054 :: TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621680129115Scrutinee_6989586621680128972Sym1 x16989586621680129110 :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (x26989586621680129111 :: k2) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621680129115Scrutinee_6989586621680128972Sym1 x16989586621680129110 :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (x26989586621680129111 :: k2) = Let6989586621680129115Scrutinee_6989586621680128972Sym2 x16989586621680129110 x26989586621680129111 :: TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621680129192Scrutinee_6989586621680128958Sym2 x06989586621680129182 x6989586621680129191 :: TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) (y6989586621680129183 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621680129192Scrutinee_6989586621680128958Sym2 x06989586621680129182 x6989586621680129191 :: TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) (y6989586621680129183 :: k1) = Let6989586621680129192Scrutinee_6989586621680128958Sym3 x06989586621680129182 x6989586621680129191 y6989586621680129183 :: TyFun k3 (TyFun k4 Bool -> Type) -> Type
type Apply (Let6989586621680129058Scrutinee_6989586621680128982Sym2 x26989586621680129054 x16989586621680129053 :: TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) (y6989586621680129055 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621680129058Scrutinee_6989586621680128982Sym2 x26989586621680129054 x16989586621680129053 :: TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) (y6989586621680129055 :: k1) = Let6989586621680129058Scrutinee_6989586621680128982Sym3 x26989586621680129054 x16989586621680129053 y6989586621680129055 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type
type Apply (Let6989586621680129115Scrutinee_6989586621680128972Sym2 x26989586621680129111 x16989586621680129110 :: TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) (y6989586621680129112 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621680129115Scrutinee_6989586621680128972Sym2 x26989586621680129111 x16989586621680129110 :: TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) (y6989586621680129112 :: k1) = Let6989586621680129115Scrutinee_6989586621680128972Sym3 x26989586621680129111 x16989586621680129110 y6989586621680129112 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type
type Apply (Let6989586621680129192Scrutinee_6989586621680128958Sym3 y6989586621680129183 x06989586621680129182 x6989586621680129191 :: TyFun k3 (TyFun k4 Bool -> Type) -> Type) (arg_69895866216801289546989586621680129178 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621680129192Scrutinee_6989586621680128958Sym3 y6989586621680129183 x06989586621680129182 x6989586621680129191 :: TyFun k3 (TyFun k4 Bool -> Type) -> Type) (arg_69895866216801289546989586621680129178 :: k3) = Let6989586621680129192Scrutinee_6989586621680128958Sym4 y6989586621680129183 x06989586621680129182 x6989586621680129191 arg_69895866216801289546989586621680129178 :: TyFun k4 Bool -> Type
type Apply (Let6989586621680129058Scrutinee_6989586621680128982Sym3 y6989586621680129055 x26989586621680129054 x16989586621680129053 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) (arg_69895866216801289766989586621680129048 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621680129058Scrutinee_6989586621680128982Sym3 y6989586621680129055 x26989586621680129054 x16989586621680129053 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) (arg_69895866216801289766989586621680129048 :: k3) = Let6989586621680129058Scrutinee_6989586621680128982Sym4 y6989586621680129055 x26989586621680129054 x16989586621680129053 arg_69895866216801289766989586621680129048 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type
type Apply (Let6989586621680129115Scrutinee_6989586621680128972Sym3 y6989586621680129112 x26989586621680129111 x16989586621680129110 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) (arg_69895866216801289666989586621680129105 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621680129115Scrutinee_6989586621680128972Sym3 y6989586621680129112 x26989586621680129111 x16989586621680129110 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) (arg_69895866216801289666989586621680129105 :: k3) = Let6989586621680129115Scrutinee_6989586621680128972Sym4 y6989586621680129112 x26989586621680129111 x16989586621680129110 arg_69895866216801289666989586621680129105 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type
type Apply (Let6989586621680129058Scrutinee_6989586621680128982Sym4 arg_69895866216801289766989586621680129048 y6989586621680129055 x26989586621680129054 x16989586621680129053 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type) (arg_69895866216801289786989586621680129049 :: k4) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621680129058Scrutinee_6989586621680128982Sym4 arg_69895866216801289766989586621680129048 y6989586621680129055 x26989586621680129054 x16989586621680129053 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type) (arg_69895866216801289786989586621680129049 :: k4) = Let6989586621680129058Scrutinee_6989586621680128982Sym5 arg_69895866216801289766989586621680129048 y6989586621680129055 x26989586621680129054 x16989586621680129053 arg_69895866216801289786989586621680129049 :: TyFun k5 Bool -> Type
type Apply (Let6989586621680129115Scrutinee_6989586621680128972Sym4 arg_69895866216801289666989586621680129105 y6989586621680129112 x26989586621680129111 x16989586621680129110 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type) (arg_69895866216801289686989586621680129106 :: k4) 
Instance details

Defined in Data.Singletons.Prelude.Enum

type Apply (Let6989586621680129115Scrutinee_6989586621680128972Sym4 arg_69895866216801289666989586621680129105 y6989586621680129112 x26989586621680129111 x16989586621680129110 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type) (arg_69895866216801289686989586621680129106 :: k4) = Let6989586621680129115Scrutinee_6989586621680128972Sym5 arg_69895866216801289666989586621680129105 y6989586621680129112 x26989586621680129111 x16989586621680129110 arg_69895866216801289686989586621680129106 :: TyFun k5 Bool -> Type
type Eval (Elem a2 as :: Bool -> Type) 
Instance details

Defined in Fcf.Data.List

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

Defined in Fcf.Data.Common

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

Defined in Fcf.Data.Common

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

Defined in Fcf.Data.Common

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

Defined in Fcf.Data.Common

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

Defined in Fcf.Utils

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

Defined in Util.Fcf

type Eval (TyEqSing a b :: Bool -> Type) = DefaultEq a b
type Eval (Guarded x ((p := y) ': ys) :: a2 -> Type) 
Instance details

Defined in Fcf.Data.Bool

type Eval (Guarded x ((p := y) ': ys) :: a2 -> Type) = Eval (If (Eval (p x)) y (Guarded x ys))
type Apply OrSym0 (a6989586621680321540 :: [Bool]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply OrSym0 (a6989586621680321540 :: [Bool]) = Or a6989586621680321540
type Apply AndSym0 (a6989586621680321544 :: [Bool]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

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

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

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.Maybe

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

Defined in Data.Singletons.Prelude.Maybe

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

Defined in Data.Singletons.Prelude.Foldable

type Apply (AndSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680742863 :: t Bool) = And a6989586621680742863
type Apply (Let6989586621680742866Scrutinee_6989586621680742628Sym0 :: TyFun (t6989586621680742381 Bool) All -> Type) (x6989586621680742865 :: t6989586621680742381 Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680742866Scrutinee_6989586621680742628Sym0 :: TyFun (t6989586621680742381 Bool) All -> Type) (x6989586621680742865 :: t6989586621680742381 Bool) = Let6989586621680742866Scrutinee_6989586621680742628 x6989586621680742865
type Apply (OrSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680742854 :: t Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (OrSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680742854 :: t Bool) = Or a6989586621680742854
type Apply (Let6989586621680742857Scrutinee_6989586621680742630Sym0 :: TyFun (t6989586621680742381 Bool) Any -> Type) (x6989586621680742856 :: t6989586621680742381 Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680742857Scrutinee_6989586621680742630Sym0 :: TyFun (t6989586621680742381 Bool) Any -> Type) (x6989586621680742856 :: t6989586621680742381 Bool) = Let6989586621680742857Scrutinee_6989586621680742630 x6989586621680742856
type Apply (Null_6989586621680921344Sym0 :: TyFun (Identity a) Bool -> Type) (a6989586621680921343 :: Identity a) 
Instance details

Defined in Data.Singletons.Prelude.Identity

type Apply (Null_6989586621680921344Sym0 :: TyFun (Identity a) Bool -> Type) (a6989586621680921343 :: Identity a) = Null_6989586621680921344 a6989586621680921343
type Apply (ListelemSym1 a6989586621680687700 :: TyFun [a] Bool -> Type) (a6989586621680687701 :: [a]) 
Instance details

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

type Apply (ListelemSym1 a6989586621680687700 :: TyFun [a] Bool -> Type) (a6989586621680687701 :: [a]) = Listelem a6989586621680687700 a6989586621680687701
type Apply (ListisPrefixOfSym1 a6989586621680687765 :: TyFun [a] Bool -> Type) (a6989586621680687766 :: [a]) 
Instance details

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

type Apply (ListisPrefixOfSym1 a6989586621680687765 :: TyFun [a] Bool -> Type) (a6989586621680687766 :: [a]) = ListisPrefixOf a6989586621680687765 a6989586621680687766
type Apply (NotElemSym1 a6989586621680321269 :: TyFun [a] Bool -> Type) (a6989586621680321270 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (NotElemSym1 a6989586621680321269 :: TyFun [a] Bool -> Type) (a6989586621680321270 :: [a]) = NotElem a6989586621680321269 a6989586621680321270
type Apply (ElemSym1 a6989586621680321276 :: TyFun [a] Bool -> Type) (a6989586621680321277 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ElemSym1 a6989586621680321276 :: TyFun [a] Bool -> Type) (a6989586621680321277 :: [a]) = Elem a6989586621680321276 a6989586621680321277
type Apply (IsPrefixOfSym1 a6989586621680321295 :: TyFun [a] Bool -> Type) (a6989586621680321296 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IsPrefixOfSym1 a6989586621680321295 :: TyFun [a] Bool -> Type) (a6989586621680321296 :: [a]) = IsPrefixOf a6989586621680321295 a6989586621680321296
type Apply (AnySym1 a6989586621680321526 :: TyFun [a] Bool -> Type) (a6989586621680321527 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (AnySym1 a6989586621680321526 :: TyFun [a] Bool -> Type) (a6989586621680321527 :: [a]) = Any a6989586621680321526 a6989586621680321527
type Apply (IsInfixOfSym1 a6989586621680321283 :: TyFun [a] Bool -> Type) (a6989586621680321284 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IsInfixOfSym1 a6989586621680321283 :: TyFun [a] Bool -> Type) (a6989586621680321284 :: [a]) = IsInfixOf a6989586621680321283 a6989586621680321284
type Apply (AllSym1 a6989586621680321533 :: TyFun [a] Bool -> Type) (a6989586621680321534 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (AllSym1 a6989586621680321533 :: TyFun [a] Bool -> Type) (a6989586621680321534 :: [a]) = All a6989586621680321533 a6989586621680321534
type Apply (IsSuffixOfSym1 a6989586621680321289 :: TyFun [a] Bool -> Type) (a6989586621680321290 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IsSuffixOfSym1 a6989586621680321289 :: TyFun [a] Bool -> Type) (a6989586621680321290 :: [a]) = IsSuffixOf a6989586621680321289 a6989586621680321290
type Apply (Elem_6989586621680921217Sym1 a6989586621680921215 :: TyFun (Identity a) Bool -> Type) (a6989586621680921216 :: Identity a) 
Instance details

Defined in Data.Singletons.Prelude.Identity

type Apply (Elem_6989586621680921217Sym1 a6989586621680921215 :: TyFun (Identity a) Bool -> Type) (a6989586621680921216 :: Identity a) = Elem_6989586621680921217 a6989586621680921215 a6989586621680921216
type Apply (Elem_bySym2 a6989586621680320413 a6989586621680320412 :: TyFun [a] Bool -> Type) (a6989586621680320414 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Elem_bySym2 a6989586621680320413 a6989586621680320412 :: TyFun [a] Bool -> Type) (a6989586621680320414 :: [a]) = Elem_by a6989586621680320413 a6989586621680320412 a6989586621680320414
type Apply (Elem_6989586621680743293Sym1 a6989586621680743291 t :: TyFun (t a) Bool -> Type) (a6989586621680743292 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680743293Sym1 a6989586621680743291 t :: TyFun (t a) Bool -> Type) (a6989586621680743292 :: t a) = Elem_6989586621680743293 a6989586621680743291 a6989586621680743292
type Apply (Null_6989586621680743249Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680743248 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Null_6989586621680743249Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680743248 :: t a) = Null_6989586621680743249 a6989586621680743248
type Apply (AnySym1 a6989586621680742841 t :: TyFun (t a) Bool -> Type) (a6989586621680742842 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AnySym1 a6989586621680742841 t :: TyFun (t a) Bool -> Type) (a6989586621680742842 :: t a) = Any a6989586621680742841 a6989586621680742842
type Apply (ElemSym1 arg6989586621680743044 t :: TyFun (t a) Bool -> Type) (arg6989586621680743045 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (ElemSym1 arg6989586621680743044 t :: TyFun (t a) Bool -> Type) (arg6989586621680743045 :: t a) = Elem arg6989586621680743044 arg6989586621680743045
type Apply (NotElemSym1 a6989586621680742770 t :: TyFun (t a) Bool -> Type) (a6989586621680742771 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (NotElemSym1 a6989586621680742770 t :: TyFun (t a) Bool -> Type) (a6989586621680742771 :: t a) = NotElem a6989586621680742770 a6989586621680742771
type Apply (NullSym0 :: TyFun (t a) Bool -> Type) (arg6989586621680743040 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (NullSym0 :: TyFun (t a) Bool -> Type) (arg6989586621680743040 :: t a) = Null arg6989586621680743040
type Apply (AllSym1 a6989586621680742828 t :: TyFun (t a) Bool -> Type) (a6989586621680742829 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AllSym1 a6989586621680742828 t :: TyFun (t a) Bool -> Type) (a6989586621680742829 :: t a) = All a6989586621680742828 a6989586621680742829
type Apply (Elem_6989586621680743413Sym1 a6989586621680743411 t :: TyFun (t a) Bool -> Type) (a6989586621680743412 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680743413Sym1 a6989586621680743411 t :: TyFun (t a) Bool -> Type) (a6989586621680743412 :: t a) = Elem_6989586621680743413 a6989586621680743411 a6989586621680743412
type Apply (Null_6989586621680743556Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680743555 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Null_6989586621680743556Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680743555 :: t a) = Null_6989586621680743556 a6989586621680743555
type Apply (Null_6989586621680743732Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680743731 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Null_6989586621680743732Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680743731 :: t a) = Null_6989586621680743732 a6989586621680743731
type Apply (Elem_6989586621680743754Sym1 a6989586621680743752 t :: TyFun (t a) Bool -> Type) (a6989586621680743753 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680743754Sym1 a6989586621680743752 t :: TyFun (t a) Bool -> Type) (a6989586621680743753 :: t a) = Elem_6989586621680743754 a6989586621680743752 a6989586621680743753
type Apply (Null_6989586621680743881Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680743880 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Null_6989586621680743881Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680743880 :: t a) = Null_6989586621680743881 a6989586621680743880
type Apply (Elem_6989586621680743921Sym1 a6989586621680743919 t :: TyFun (t a) Bool -> Type) (a6989586621680743920 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680743921Sym1 a6989586621680743919 t :: TyFun (t a) Bool -> Type) (a6989586621680743920 :: t a) = Elem_6989586621680743921 a6989586621680743919 a6989586621680743920
type Apply (Null_6989586621680744048Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680744047 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Null_6989586621680744048Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680744047 :: t a) = Null_6989586621680744048 a6989586621680744047
type Apply (Elem_6989586621680744088Sym1 a6989586621680744086 t :: TyFun (t a) Bool -> Type) (a6989586621680744087 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Elem_6989586621680744088Sym1 a6989586621680744086 t :: TyFun (t a) Bool -> Type) (a6989586621680744087 :: t a) = Elem_6989586621680744088 a6989586621680744086 a6989586621680744087
type Apply (Null_6989586621680744215Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680744214 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Null_6989586621680744215Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680744214 :: t a) = Null_6989586621680744215 a6989586621680744214
type Apply (ListisPrefixOfSym0 :: TyFun [a6989586621680686805] ([a6989586621680686805] ~> Bool) -> Type) (a6989586621680687765 :: [a6989586621680686805]) 
Instance details

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

type Apply (ListisPrefixOfSym0 :: TyFun [a6989586621680686805] ([a6989586621680686805] ~> Bool) -> Type) (a6989586621680687765 :: [a6989586621680686805]) = ListisPrefixOfSym1 a6989586621680687765
type Apply (IsPrefixOfSym0 :: TyFun [a6989586621680316403] ([a6989586621680316403] ~> Bool) -> Type) (a6989586621680321295 :: [a6989586621680316403]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IsPrefixOfSym0 :: TyFun [a6989586621680316403] ([a6989586621680316403] ~> Bool) -> Type) (a6989586621680321295 :: [a6989586621680316403]) = IsPrefixOfSym1 a6989586621680321295
type Apply (IsInfixOfSym0 :: TyFun [a6989586621680316401] ([a6989586621680316401] ~> Bool) -> Type) (a6989586621680321283 :: [a6989586621680316401]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IsInfixOfSym0 :: TyFun [a6989586621680316401] ([a6989586621680316401] ~> Bool) -> Type) (a6989586621680321283 :: [a6989586621680316401]) = IsInfixOfSym1 a6989586621680321283
type Apply (IsSuffixOfSym0 :: TyFun [a6989586621680316402] ([a6989586621680316402] ~> Bool) -> Type) (a6989586621680321289 :: [a6989586621680316402]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IsSuffixOfSym0 :: TyFun [a6989586621680316402] ([a6989586621680316402] ~> Bool) -> Type) (a6989586621680321289 :: [a6989586621680316402]) = IsSuffixOfSym1 a6989586621680321289
type Apply (Let6989586621680320760Scrutinee_6989586621680316995Sym1 x6989586621680320758 :: TyFun [a6989586621680316437] (TyFun (k1 ~> Bool) (TyFun k Bool -> Type) -> Type) -> Type) (xs6989586621680320759 :: [a6989586621680316437]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680320760Scrutinee_6989586621680316995Sym1 x6989586621680320758 :: TyFun [a6989586621680316437] (TyFun (k1 ~> Bool) (TyFun k Bool -> Type) -> Type) -> Type) (xs6989586621680320759 :: [a6989586621680316437]) = Let6989586621680320760Scrutinee_6989586621680316995Sym2 x6989586621680320758 xs6989586621680320759 :: TyFun (k1 ~> Bool) (TyFun k Bool -> Type) -> Type
type Apply (Let6989586621680320438Scrutinee_6989586621680317023Sym2 ys6989586621680320436 y6989586621680320435 :: TyFun [k1] (TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type) -> Type) (xs6989586621680320437 :: [k1]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680320438Scrutinee_6989586621680317023Sym2 ys6989586621680320436 y6989586621680320435 :: TyFun [k1] (TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type) -> Type) (xs6989586621680320437 :: [k1]) = Let6989586621680320438Scrutinee_6989586621680317023Sym3 ys6989586621680320436 y6989586621680320435 xs6989586621680320437 :: TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type
type Apply (Let6989586621680320459Scrutinee_6989586621680317021Sym2 xs6989586621680320457 x6989586621680320456 :: TyFun [k1] (TyFun k3 Bool -> Type) -> Type) (ls6989586621680320458 :: [k1]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680320459Scrutinee_6989586621680317021Sym2 xs6989586621680320457 x6989586621680320456 :: TyFun [k1] (TyFun k3 Bool -> Type) -> Type) (ls6989586621680320458 :: [k1]) = Let6989586621680320459Scrutinee_6989586621680317021Sym3 xs6989586621680320457 x6989586621680320456 ls6989586621680320458 :: TyFun k3 Bool -> Type
type Arg (a -> Bool) 
Instance details

Defined in Test.Hspec.Core.Example

type Arg (a -> Bool) = a
type Apply (IsRightSym0 :: TyFun (Either a b) Bool -> Type) (a6989586621680725481 :: Either a b) 
Instance details

Defined in Data.Singletons.Prelude.Either

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

Defined in Data.Singletons.Prelude.Either

type Apply (IsLeftSym0 :: TyFun (Either a b) Bool -> Type) (a6989586621680725483 :: Either a b) = IsLeft a6989586621680725483
type Apply (TFHelper_6989586621681108278Sym1 a6989586621681108276 :: TyFun (Arg a b) Bool -> Type) (a6989586621681108277 :: Arg a b) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Apply (TFHelper_6989586621681108278Sym1 a6989586621681108276 :: TyFun (Arg a b) Bool -> Type) (a6989586621681108277 :: Arg a b) = TFHelper_6989586621681108278 a6989586621681108276 a6989586621681108277
type Apply (ListnubBySym0 :: TyFun (a6989586621680686799 ~> (a6989586621680686799 ~> Bool)) ([a6989586621680686799] ~> [a6989586621680686799]) -> Type) (a6989586621680687730 :: a6989586621680686799 ~> (a6989586621680686799 ~> Bool)) 
Instance details

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

type Apply (ListnubBySym0 :: TyFun (a6989586621680686799 ~> (a6989586621680686799 ~> Bool)) ([a6989586621680686799] ~> [a6989586621680686799]) -> Type) (a6989586621680687730 :: a6989586621680686799 ~> (a6989586621680686799 ~> Bool)) = ListnubBySym1 a6989586621680687730
type Apply (ListpartitionSym0 :: TyFun (a6989586621680686807 ~> Bool) ([a6989586621680686807] ~> ([a6989586621680686807], [a6989586621680686807])) -> Type) (a6989586621680687785 :: a6989586621680686807 ~> Bool) 
Instance details

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

type Apply (ListpartitionSym0 :: TyFun (a6989586621680686807 ~> Bool) ([a6989586621680686807] ~> ([a6989586621680686807], [a6989586621680686807])) -> Type) (a6989586621680687785 :: a6989586621680686807 ~> Bool) = ListpartitionSym1 a6989586621680687785
type Apply (ListfilterSym0 :: TyFun (a6989586621680686808 ~> Bool) ([a6989586621680686808] ~> [a6989586621680686808]) -> Type) (a6989586621680687795 :: a6989586621680686808 ~> Bool) 
Instance details

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

type Apply (ListfilterSym0 :: TyFun (a6989586621680686808 ~> Bool) ([a6989586621680686808] ~> [a6989586621680686808]) -> Type) (a6989586621680687795 :: a6989586621680686808 ~> Bool) = ListfilterSym1 a6989586621680687795
type Apply (ListspanSym0 :: TyFun (a6989586621680686809 ~> Bool) ([a6989586621680686809] ~> ([a6989586621680686809], [a6989586621680686809])) -> Type) (a6989586621680687805 :: a6989586621680686809 ~> Bool) 
Instance details

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

type Apply (ListspanSym0 :: TyFun (a6989586621680686809 ~> Bool) ([a6989586621680686809] ~> ([a6989586621680686809], [a6989586621680686809])) -> Type) (a6989586621680687805 :: a6989586621680686809 ~> Bool) = ListspanSym1 a6989586621680687805
type Apply (ListdropWhileSym0 :: TyFun (a6989586621680686810 ~> Bool) ([a6989586621680686810] ~> [a6989586621680686810]) -> Type) (a6989586621680687815 :: a6989586621680686810 ~> Bool) 
Instance details

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

type Apply (ListdropWhileSym0 :: TyFun (a6989586621680686810 ~> Bool) ([a6989586621680686810] ~> [a6989586621680686810]) -> Type) (a6989586621680687815 :: a6989586621680686810 ~> Bool) = ListdropWhileSym1 a6989586621680687815
type Apply (ListtakeWhileSym0 :: TyFun (a6989586621680686811 ~> Bool) ([a6989586621680686811] ~> [a6989586621680686811]) -> Type) (a6989586621680687825 :: a6989586621680686811 ~> Bool) 
Instance details

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

type Apply (ListtakeWhileSym0 :: TyFun (a6989586621680686811 ~> Bool) ([a6989586621680686811] ~> [a6989586621680686811]) -> Type) (a6989586621680687825 :: a6989586621680686811 ~> Bool) = ListtakeWhileSym1 a6989586621680687825
type Apply (Elem_bySym0 :: TyFun (a6989586621680316317 ~> (a6989586621680316317 ~> Bool)) (a6989586621680316317 ~> ([a6989586621680316317] ~> Bool)) -> Type) (a6989586621680320412 :: a6989586621680316317 ~> (a6989586621680316317 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Elem_bySym0 :: TyFun (a6989586621680316317 ~> (a6989586621680316317 ~> Bool)) (a6989586621680316317 ~> ([a6989586621680316317] ~> Bool)) -> Type) (a6989586621680320412 :: a6989586621680316317 ~> (a6989586621680316317 ~> Bool)) = Elem_bySym1 a6989586621680320412
type Apply (NubBySym0 :: TyFun (a6989586621680316318 ~> (a6989586621680316318 ~> Bool)) ([a6989586621680316318] ~> [a6989586621680316318]) -> Type) (a6989586621680320422 :: a6989586621680316318 ~> (a6989586621680316318 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (NubBySym0 :: TyFun (a6989586621680316318 ~> (a6989586621680316318 ~> Bool)) ([a6989586621680316318] ~> [a6989586621680316318]) -> Type) (a6989586621680320422 :: a6989586621680316318 ~> (a6989586621680316318 ~> Bool)) = NubBySym1 a6989586621680320422
type Apply (SelectSym0 :: TyFun (a6989586621680316326 ~> Bool) (a6989586621680316326 ~> (([a6989586621680316326], [a6989586621680316326]) ~> ([a6989586621680316326], [a6989586621680316326]))) -> Type) (a6989586621680320528 :: a6989586621680316326 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (SelectSym0 :: TyFun (a6989586621680316326 ~> Bool) (a6989586621680316326 ~> (([a6989586621680316326], [a6989586621680316326]) ~> ([a6989586621680316326], [a6989586621680316326]))) -> Type) (a6989586621680320528 :: a6989586621680316326 ~> Bool) = SelectSym1 a6989586621680320528
type Apply (PartitionSym0 :: TyFun (a6989586621680316327 ~> Bool) ([a6989586621680316327] ~> ([a6989586621680316327], [a6989586621680316327])) -> Type) (a6989586621680320546 :: a6989586621680316327 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (PartitionSym0 :: TyFun (a6989586621680316327 ~> Bool) ([a6989586621680316327] ~> ([a6989586621680316327], [a6989586621680316327])) -> Type) (a6989586621680320546 :: a6989586621680316327 ~> Bool) = PartitionSym1 a6989586621680320546
type Apply (BreakSym0 :: TyFun (a6989586621680316339 ~> Bool) ([a6989586621680316339] ~> ([a6989586621680316339], [a6989586621680316339])) -> Type) (a6989586621680320662 :: a6989586621680316339 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (BreakSym0 :: TyFun (a6989586621680316339 ~> Bool) ([a6989586621680316339] ~> ([a6989586621680316339], [a6989586621680316339])) -> Type) (a6989586621680320662 :: a6989586621680316339 ~> Bool) = BreakSym1 a6989586621680320662
type Apply (Let6989586621680320680YsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621680320667 :: k ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680320680YsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621680320667 :: k ~> Bool) = Let6989586621680320680YsSym1 p6989586621680320667
type Apply (Let6989586621680320680ZsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621680320667 :: k ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680320680ZsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621680320667 :: k ~> Bool) = Let6989586621680320680ZsSym1 p6989586621680320667
type Apply (Let6989586621680320680X_6989586621680320681Sym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] ([k], [k]) -> Type) -> Type) -> Type) (p6989586621680320667 :: k ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680320680X_6989586621680320681Sym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] ([k], [k]) -> Type) -> Type) -> Type) (p6989586621680320667 :: k ~> Bool) = Let6989586621680320680X_6989586621680320681Sym1 p6989586621680320667
type Apply (SpanSym0 :: TyFun (a6989586621680316340 ~> Bool) ([a6989586621680316340] ~> ([a6989586621680316340], [a6989586621680316340])) -> Type) (a6989586621680320705 :: a6989586621680316340 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (SpanSym0 :: TyFun (a6989586621680316340 ~> Bool) ([a6989586621680316340] ~> ([a6989586621680316340], [a6989586621680316340])) -> Type) (a6989586621680320705 :: a6989586621680316340 ~> Bool) = SpanSym1 a6989586621680320705
type Apply (Let6989586621680320723YsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621680320710 :: k ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680320723YsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621680320710 :: k ~> Bool) = Let6989586621680320723YsSym1 p6989586621680320710
type Apply (Let6989586621680320723ZsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621680320710 :: k ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680320723ZsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621680320710 :: k ~> Bool) = Let6989586621680320723ZsSym1 p6989586621680320710
type Apply (Let6989586621680320723X_6989586621680320724Sym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] ([k], [k]) -> Type) -> Type) -> Type) (p6989586621680320710 :: k ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680320723X_6989586621680320724Sym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] ([k], [k]) -> Type) -> Type) -> Type) (p6989586621680320710 :: k ~> Bool) = Let6989586621680320723X_6989586621680320724Sym1 p6989586621680320710
type Apply (GroupBySym0 :: TyFun (a6989586621680316330 ~> (a6989586621680316330 ~> Bool)) ([a6989586621680316330] ~> [[a6989586621680316330]]) -> Type) (a6989586621680320569 :: a6989586621680316330 ~> (a6989586621680316330 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (GroupBySym0 :: TyFun (a6989586621680316330 ~> (a6989586621680316330 ~> Bool)) ([a6989586621680316330] ~> [[a6989586621680316330]]) -> Type) (a6989586621680320569 :: a6989586621680316330 ~> (a6989586621680316330 ~> Bool)) = GroupBySym1 a6989586621680320569
type Apply (DropWhileSym0 :: TyFun (a6989586621680316342 ~> Bool) ([a6989586621680316342] ~> [a6989586621680316342]) -> Type) (a6989586621680320774 :: a6989586621680316342 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DropWhileSym0 :: TyFun (a6989586621680316342 ~> Bool) ([a6989586621680316342] ~> [a6989586621680316342]) -> Type) (a6989586621680320774 :: a6989586621680316342 ~> Bool) = DropWhileSym1 a6989586621680320774
type Apply (TakeWhileSym0 :: TyFun (a6989586621680316343 ~> Bool) ([a6989586621680316343] ~> [a6989586621680316343]) -> Type) (a6989586621680320792 :: a6989586621680316343 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (TakeWhileSym0 :: TyFun (a6989586621680316343 ~> Bool) ([a6989586621680316343] ~> [a6989586621680316343]) -> Type) (a6989586621680320792 :: a6989586621680316343 ~> Bool) = TakeWhileSym1 a6989586621680320792
type Apply (FilterSym0 :: TyFun (a6989586621680316351 ~> Bool) ([a6989586621680316351] ~> [a6989586621680316351]) -> Type) (a6989586621680320906 :: a6989586621680316351 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FilterSym0 :: TyFun (a6989586621680316351 ~> Bool) ([a6989586621680316351] ~> [a6989586621680316351]) -> Type) (a6989586621680320906 :: a6989586621680316351 ~> Bool) = FilterSym1 a6989586621680320906
type Apply (FindSym0 :: TyFun (a6989586621680316350 ~> Bool) ([a6989586621680316350] ~> Maybe a6989586621680316350) -> Type) (a6989586621680320898 :: a6989586621680316350 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FindSym0 :: TyFun (a6989586621680316350 ~> Bool) ([a6989586621680316350] ~> Maybe a6989586621680316350) -> Type) (a6989586621680320898 :: a6989586621680316350 ~> Bool) = FindSym1 a6989586621680320898
type Apply (DeleteBySym0 :: TyFun (a6989586621680316357 ~> (a6989586621680316357 ~> Bool)) (a6989586621680316357 ~> ([a6989586621680316357] ~> [a6989586621680316357])) -> Type) (a6989586621680321026 :: a6989586621680316357 ~> (a6989586621680316357 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DeleteBySym0 :: TyFun (a6989586621680316357 ~> (a6989586621680316357 ~> Bool)) (a6989586621680316357 ~> ([a6989586621680316357] ~> [a6989586621680316357])) -> Type) (a6989586621680321026 :: a6989586621680316357 ~> (a6989586621680316357 ~> Bool)) = DeleteBySym1 a6989586621680321026
type Apply (DeleteFirstsBySym0 :: TyFun (a6989586621680316356 ~> (a6989586621680316356 ~> Bool)) ([a6989586621680316356] ~> ([a6989586621680316356] ~> [a6989586621680316356])) -> Type) (a6989586621680321013 :: a6989586621680316356 ~> (a6989586621680316356 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DeleteFirstsBySym0 :: TyFun (a6989586621680316356 ~> (a6989586621680316356 ~> Bool)) ([a6989586621680316356] ~> ([a6989586621680316356] ~> [a6989586621680316356])) -> Type) (a6989586621680321013 :: a6989586621680316356 ~> (a6989586621680316356 ~> Bool)) = DeleteFirstsBySym1 a6989586621680321013
type Apply (UnionBySym0 :: TyFun (a6989586621680316316 ~> (a6989586621680316316 ~> Bool)) ([a6989586621680316316] ~> ([a6989586621680316316] ~> [a6989586621680316316])) -> Type) (a6989586621680320403 :: a6989586621680316316 ~> (a6989586621680316316 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (UnionBySym0 :: TyFun (a6989586621680316316 ~> (a6989586621680316316 ~> Bool)) ([a6989586621680316316] ~> ([a6989586621680316316] ~> [a6989586621680316316])) -> Type) (a6989586621680320403 :: a6989586621680316316 ~> (a6989586621680316316 ~> Bool)) = UnionBySym1 a6989586621680320403
type Apply (FindIndicesSym0 :: TyFun (a6989586621680316346 ~> Bool) ([a6989586621680316346] ~> [Nat]) -> Type) (a6989586621680320848 :: a6989586621680316346 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FindIndicesSym0 :: TyFun (a6989586621680316346 ~> Bool) ([a6989586621680316346] ~> [Nat]) -> Type) (a6989586621680320848 :: a6989586621680316346 ~> Bool) = FindIndicesSym1 a6989586621680320848
type Apply (FindIndexSym0 :: TyFun (a6989586621680316347 ~> Bool) ([a6989586621680316347] ~> Maybe Nat) -> Type) (a6989586621680320874 :: a6989586621680316347 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FindIndexSym0 :: TyFun (a6989586621680316347 ~> Bool) ([a6989586621680316347] ~> Maybe Nat) -> Type) (a6989586621680320874 :: a6989586621680316347 ~> Bool) = FindIndexSym1 a6989586621680320874
type Apply (AnySym0 :: TyFun (a6989586621680316420 ~> Bool) ([a6989586621680316420] ~> Bool) -> Type) (a6989586621680321526 :: a6989586621680316420 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (AnySym0 :: TyFun (a6989586621680316420 ~> Bool) ([a6989586621680316420] ~> Bool) -> Type) (a6989586621680321526 :: a6989586621680316420 ~> Bool) = AnySym1 a6989586621680321526
type Apply (IntersectBySym0 :: TyFun (a6989586621680316344 ~> (a6989586621680316344 ~> Bool)) ([a6989586621680316344] ~> ([a6989586621680316344] ~> [a6989586621680316344])) -> Type) (a6989586621680320806 :: a6989586621680316344 ~> (a6989586621680316344 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (IntersectBySym0 :: TyFun (a6989586621680316344 ~> (a6989586621680316344 ~> Bool)) ([a6989586621680316344] ~> ([a6989586621680316344] ~> [a6989586621680316344])) -> Type) (a6989586621680320806 :: a6989586621680316344 ~> (a6989586621680316344 ~> Bool)) = IntersectBySym1 a6989586621680320806
type Apply (AllSym0 :: TyFun (a6989586621680316421 ~> Bool) ([a6989586621680316421] ~> Bool) -> Type) (a6989586621680321533 :: a6989586621680316421 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (AllSym0 :: TyFun (a6989586621680316421 ~> Bool) ([a6989586621680316421] ~> Bool) -> Type) (a6989586621680321533 :: a6989586621680316421 ~> Bool) = AllSym1 a6989586621680321533
type Apply (DropWhileEndSym0 :: TyFun (a6989586621680316341 ~> Bool) ([a6989586621680316341] ~> [a6989586621680316341]) -> Type) (a6989586621680320748 :: a6989586621680316341 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (DropWhileEndSym0 :: TyFun (a6989586621680316341 ~> Bool) ([a6989586621680316341] ~> [a6989586621680316341]) -> Type) (a6989586621680320748 :: a6989586621680316341 ~> Bool) = DropWhileEndSym1 a6989586621680320748
type Apply (UntilSym0 :: TyFun (a6989586621679941593 ~> Bool) ((a6989586621679941593 ~> a6989586621679941593) ~> (a6989586621679941593 ~> a6989586621679941593)) -> Type) (a6989586621679941718 :: a6989586621679941593 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (UntilSym0 :: TyFun (a6989586621679941593 ~> Bool) ((a6989586621679941593 ~> a6989586621679941593) ~> (a6989586621679941593 ~> a6989586621679941593)) -> Type) (a6989586621679941718 :: a6989586621679941593 ~> Bool) = UntilSym1 a6989586621679941718
type Apply (TFHelper_6989586621681108278Sym0 :: TyFun (Arg a6989586621681107123 b6989586621681107124) (Arg a6989586621681107123 b6989586621681107124 ~> Bool) -> Type) (a6989586621681108276 :: Arg a6989586621681107123 b6989586621681107124) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Apply (TFHelper_6989586621681108278Sym0 :: TyFun (Arg a6989586621681107123 b6989586621681107124) (Arg a6989586621681107123 b6989586621681107124 ~> Bool) -> Type) (a6989586621681108276 :: Arg a6989586621681107123 b6989586621681107124) = TFHelper_6989586621681108278Sym1 a6989586621681108276
type Apply (MfilterSym0 :: TyFun (a6989586621681401666 ~> Bool) (m6989586621681401665 a6989586621681401666 ~> m6989586621681401665 a6989586621681401666) -> Type) (a6989586621681401985 :: a6989586621681401666 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Monad

type Apply (MfilterSym0 :: TyFun (a6989586621681401666 ~> Bool) (m6989586621681401665 a6989586621681401666 ~> m6989586621681401665 a6989586621681401666) -> Type) (a6989586621681401985 :: a6989586621681401666 ~> Bool) = MfilterSym1 a6989586621681401985 m6989586621681401665 :: TyFun (m6989586621681401665 a6989586621681401666) (m6989586621681401665 a6989586621681401666) -> Type
type Apply (FilterMSym0 :: TyFun (a6989586621681401704 ~> m6989586621681401703 Bool) ([a6989586621681401704] ~> m6989586621681401703 [a6989586621681401704]) -> Type) (a6989586621681402151 :: a6989586621681401704 ~> m6989586621681401703 Bool) 
Instance details

Defined in Data.Singletons.Prelude.Monad

type Apply (FilterMSym0 :: TyFun (a6989586621681401704 ~> m6989586621681401703 Bool) ([a6989586621681401704] ~> m6989586621681401703 [a6989586621681401704]) -> Type) (a6989586621681402151 :: a6989586621681401704 ~> m6989586621681401703 Bool) = FilterMSym1 a6989586621681402151
type Apply (Let6989586621680320428NubBy'Sym0 :: TyFun (k1 ~> (k1 ~> Bool)) (TyFun k (TyFun [k1] ([k1] ~> [k1]) -> Type) -> Type) -> Type) (eq6989586621680320426 :: k1 ~> (k1 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680320428NubBy'Sym0 :: TyFun (k1 ~> (k1 ~> Bool)) (TyFun k (TyFun [k1] ([k1] ~> [k1]) -> Type) -> Type) -> Type) (eq6989586621680320426 :: k1 ~> (k1 ~> Bool)) = Let6989586621680320428NubBy'Sym1 eq6989586621680320426 :: TyFun k (TyFun [k1] ([k1] ~> [k1]) -> Type) -> Type
type Apply (Let6989586621680320576YsSym0 :: TyFun (k1 ~> (a6989586621680316340 ~> Bool)) (TyFun k1 (TyFun [a6989586621680316340] [a6989586621680316340] -> Type) -> Type) -> Type) (eq6989586621680320573 :: k1 ~> (a6989586621680316340 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680320576YsSym0 :: TyFun (k1 ~> (a6989586621680316340 ~> Bool)) (TyFun k1 (TyFun [a6989586621680316340] [a6989586621680316340] -> Type) -> Type) -> Type) (eq6989586621680320573 :: k1 ~> (a6989586621680316340 ~> Bool)) = Let6989586621680320576YsSym1 eq6989586621680320573
type Apply (Let6989586621680320576ZsSym0 :: TyFun (k1 ~> (a6989586621680316340 ~> Bool)) (TyFun k1 (TyFun [a6989586621680316340] [a6989586621680316340] -> Type) -> Type) -> Type) (eq6989586621680320573 :: k1 ~> (a6989586621680316340 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680320576ZsSym0 :: TyFun (k1 ~> (a6989586621680316340 ~> Bool)) (TyFun k1 (TyFun [a6989586621680316340] [a6989586621680316340] -> Type) -> Type) -> Type) (eq6989586621680320573 :: k1 ~> (a6989586621680316340 ~> Bool)) = Let6989586621680320576ZsSym1 eq6989586621680320573
type Apply (Let6989586621680320576X_6989586621680320577Sym0 :: TyFun (k1 ~> (a6989586621680316340 ~> Bool)) (TyFun k1 (TyFun [a6989586621680316340] ([a6989586621680316340], [a6989586621680316340]) -> Type) -> Type) -> Type) (eq6989586621680320573 :: k1 ~> (a6989586621680316340 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680320576X_6989586621680320577Sym0 :: TyFun (k1 ~> (a6989586621680316340 ~> Bool)) (TyFun k1 (TyFun [a6989586621680316340] ([a6989586621680316340], [a6989586621680316340]) -> Type) -> Type) -> Type) (eq6989586621680320573 :: k1 ~> (a6989586621680316340 ~> Bool)) = Let6989586621680320576X_6989586621680320577Sym1 eq6989586621680320573
type Apply (Lambda_6989586621680320756Sym0 :: TyFun (a6989586621680316437 ~> Bool) (TyFun k (TyFun a6989586621680316437 (TyFun [a6989586621680316437] [a6989586621680316437] -> Type) -> Type) -> Type) -> Type) (p6989586621680320754 :: a6989586621680316437 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Lambda_6989586621680320756Sym0 :: TyFun (a6989586621680316437 ~> Bool) (TyFun k (TyFun a6989586621680316437 (TyFun [a6989586621680316437] [a6989586621680316437] -> Type) -> Type) -> Type) -> Type) (p6989586621680320754 :: a6989586621680316437 ~> Bool) = Lambda_6989586621680320756Sym1 p6989586621680320754 :: TyFun k (TyFun a6989586621680316437 (TyFun [a6989586621680316437] [a6989586621680316437] -> Type) -> Type) -> Type
type Apply (Lambda_6989586621680742750Sym0 :: TyFun (a6989586621679087424 ~> Bool) (TyFun k (TyFun a6989586621679087424 (First a6989586621679087424) -> Type) -> Type) -> Type) (p6989586621680742747 :: a6989586621679087424 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Lambda_6989586621680742750Sym0 :: TyFun (a6989586621679087424 ~> Bool) (TyFun k (TyFun a6989586621679087424 (First a6989586621679087424) -> Type) -> Type) -> Type) (p6989586621680742747 :: a6989586621679087424 ~> Bool) = Lambda_6989586621680742750Sym1 p6989586621680742747 :: TyFun k (TyFun a6989586621679087424 (First a6989586621679087424) -> Type) -> Type
type Apply (AnySym0 :: TyFun (a6989586621680742300 ~> Bool) (t6989586621680742299 a6989586621680742300 ~> Bool) -> Type) (a6989586621680742841 :: a6989586621680742300 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AnySym0 :: TyFun (a6989586621680742300 ~> Bool) (t6989586621680742299 a6989586621680742300 ~> Bool) -> Type) (a6989586621680742841 :: a6989586621680742300 ~> Bool) = AnySym1 a6989586621680742841 t6989586621680742299 :: TyFun (t6989586621680742299 a6989586621680742300) Bool -> Type
type Apply (Let6989586621680742847Scrutinee_6989586621680742632Sym0 :: TyFun (a6989586621680742384 ~> Bool) (TyFun (t6989586621680742381 a6989586621680742384) Any -> Type) -> Type) (p6989586621680742845 :: a6989586621680742384 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680742847Scrutinee_6989586621680742632Sym0 :: TyFun (a6989586621680742384 ~> Bool) (TyFun (t6989586621680742381 a6989586621680742384) Any -> Type) -> Type) (p6989586621680742845 :: a6989586621680742384 ~> Bool) = Let6989586621680742847Scrutinee_6989586621680742632Sym1 p6989586621680742845 :: TyFun (t6989586621680742381 a6989586621680742384) Any -> Type
type Apply (AllSym0 :: TyFun (a6989586621680742298 ~> Bool) (t6989586621680742297 a6989586621680742298 ~> Bool) -> Type) (a6989586621680742828 :: a6989586621680742298 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (AllSym0 :: TyFun (a6989586621680742298 ~> Bool) (t6989586621680742297 a6989586621680742298 ~> Bool) -> Type) (a6989586621680742828 :: a6989586621680742298 ~> Bool) = AllSym1 a6989586621680742828 t6989586621680742297 :: TyFun (t6989586621680742297 a6989586621680742298) Bool -> Type
type Apply (Let6989586621680742834Scrutinee_6989586621680742634Sym0 :: TyFun (a6989586621680742384 ~> Bool) (TyFun (t6989586621680742381 a6989586621680742384) All -> Type) -> Type) (p6989586621680742832 :: a6989586621680742384 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680742834Scrutinee_6989586621680742634Sym0 :: TyFun (a6989586621680742384 ~> Bool) (TyFun (t6989586621680742381 a6989586621680742384) All -> Type) -> Type) (p6989586621680742832 :: a6989586621680742384 ~> Bool) = Let6989586621680742834Scrutinee_6989586621680742634Sym1 p6989586621680742832 :: TyFun (t6989586621680742381 a6989586621680742384) All -> Type
type Apply (FindSym0 :: TyFun (a6989586621680742290 ~> Bool) (t6989586621680742289 a6989586621680742290 ~> Maybe a6989586621680742290) -> Type) (a6989586621680742743 :: a6989586621680742290 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FindSym0 :: TyFun (a6989586621680742290 ~> Bool) (t6989586621680742289 a6989586621680742290 ~> Maybe a6989586621680742290) -> Type) (a6989586621680742743 :: a6989586621680742290 ~> Bool) = FindSym1 a6989586621680742743 t6989586621680742289 :: TyFun (t6989586621680742289 a6989586621680742290) (Maybe a6989586621680742290) -> Type
type Apply (Let6989586621680742749Scrutinee_6989586621680742640Sym0 :: TyFun (a6989586621680742384 ~> Bool) (TyFun (t6989586621680742381 a6989586621680742384) (First a6989586621680742384) -> Type) -> Type) (p6989586621680742747 :: a6989586621680742384 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680742749Scrutinee_6989586621680742640Sym0 :: TyFun (a6989586621680742384 ~> Bool) (TyFun (t6989586621680742381 a6989586621680742384) (First a6989586621680742384) -> Type) -> Type) (p6989586621680742747 :: a6989586621680742384 ~> Bool) = Let6989586621680742749Scrutinee_6989586621680742640Sym1 p6989586621680742747 :: TyFun (t6989586621680742381 a6989586621680742384) (First a6989586621680742384) -> Type
type Apply (Let6989586621679941729GoSym0 :: TyFun (k1 ~> Bool) (TyFun (k1 ~> k1) (TyFun k2 (TyFun k1 k1 -> Type) -> Type) -> Type) -> Type) (p6989586621679941726 :: k1 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Base

type Apply (Let6989586621679941729GoSym0 :: TyFun (k1 ~> Bool) (TyFun (k1 ~> k1) (TyFun k2 (TyFun k1 k1 -> Type) -> Type) -> Type) -> Type) (p6989586621679941726 :: k1 ~> Bool) = Let6989586621679941729GoSym1 p6989586621679941726 :: TyFun (k1 ~> k1) (TyFun k2 (TyFun k1 k1 -> Type) -> Type) -> Type
type Apply (Lambda_6989586621681401991Sym0 :: TyFun (k1 ~> Bool) (TyFun k (TyFun k1 (m6989586621679962831 k1) -> Type) -> Type) -> Type) (p6989586621681401989 :: k1 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Monad

type Apply (Lambda_6989586621681401991Sym0 :: TyFun (k1 ~> Bool) (TyFun k (TyFun k1 (m6989586621679962831 k1) -> Type) -> Type) -> Type) (p6989586621681401989 :: k1 ~> Bool) = Lambda_6989586621681401991Sym1 p6989586621681401989 :: TyFun k (TyFun k1 (m6989586621679962831 k1) -> Type) -> Type
type Apply (Lambda_6989586621681402159Sym0 :: TyFun (k2 ~> f6989586621679962807 Bool) (TyFun k3 (TyFun k2 (TyFun (f6989586621679962807 [k2]) (f6989586621679962807 [k2]) -> Type) -> Type) -> Type) -> Type) (p6989586621681402157 :: k2 ~> f6989586621679962807 Bool) 
Instance details

Defined in Data.Singletons.Prelude.Monad

type Apply (Lambda_6989586621681402159Sym0 :: TyFun (k2 ~> f6989586621679962807 Bool) (TyFun k3 (TyFun k2 (TyFun (f6989586621679962807 [k2]) (f6989586621679962807 [k2]) -> Type) -> Type) -> Type) -> Type) (p6989586621681402157 :: k2 ~> f6989586621679962807 Bool) = Lambda_6989586621681402159Sym1 p6989586621681402157 :: TyFun k3 (TyFun k2 (TyFun (f6989586621679962807 [k2]) (f6989586621679962807 [k2]) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621680320828Sym0 :: TyFun (b6989586621679962835 ~> (a6989586621680316420 ~> Bool)) (TyFun k1 (TyFun k2 (TyFun a6989586621680316420 (TyFun [a6989586621680316420] (TyFun b6989586621679962835 (m6989586621679962831 b6989586621679962835) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (eq6989586621680320812 :: b6989586621679962835 ~> (a6989586621680316420 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Lambda_6989586621680320828Sym0 :: TyFun (b6989586621679962835 ~> (a6989586621680316420 ~> Bool)) (TyFun k1 (TyFun k2 (TyFun a6989586621680316420 (TyFun [a6989586621680316420] (TyFun b6989586621679962835 (m6989586621679962831 b6989586621679962835) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (eq6989586621680320812 :: b6989586621679962835 ~> (a6989586621680316420 ~> Bool)) = Lambda_6989586621680320828Sym1 eq6989586621680320812 :: TyFun k1 (TyFun k2 (TyFun a6989586621680316420 (TyFun [a6989586621680316420] (TyFun b6989586621679962835 (m6989586621679962831 b6989586621679962835) -> Type) -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621680320760Scrutinee_6989586621680316995Sym2 xs6989586621680320759 x6989586621680320758 :: TyFun (k1 ~> Bool) (TyFun k Bool -> Type) -> Type) (p6989586621680320754 :: k1 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680320760Scrutinee_6989586621680316995Sym2 xs6989586621680320759 x6989586621680320758 :: TyFun (k1 ~> Bool) (TyFun k Bool -> Type) -> Type) (p6989586621680320754 :: k1 ~> Bool) = Let6989586621680320760Scrutinee_6989586621680316995Sym3 xs6989586621680320759 x6989586621680320758 p6989586621680320754 :: TyFun k Bool -> Type
type Apply (Let6989586621680320438Scrutinee_6989586621680317023Sym3 xs6989586621680320437 ys6989586621680320436 y6989586621680320435 :: TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type) (eq6989586621680320426 :: k1 ~> (k1 ~> Bool)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (Let6989586621680320438Scrutinee_6989586621680317023Sym3 xs6989586621680320437 ys6989586621680320436 y6989586621680320435 :: TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type) (eq6989586621680320426 :: k1 ~> (k1 ~> Bool)) = Let6989586621680320438Scrutinee_6989586621680317023Sym4 xs6989586621680320437 ys6989586621680320436 y6989586621680320435 eq6989586621680320426 :: TyFun k3 Bool -> Type

data ByteString #

A space-efficient representation of a Word8 vector, supporting many efficient operations.

A ByteString contains 8-bit bytes, or by using the operations from Data.ByteString.Char8 it can be interpreted as containing 8-bit characters.

Instances

Instances details
Eq ByteString 
Instance details

Defined in Data.ByteString.Internal

Data ByteString 
Instance details

Defined in Data.ByteString.Internal

Methods

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

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

toConstr :: ByteString -> Constr #

dataTypeOf :: ByteString -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ByteString 
Instance details

Defined in Data.ByteString.Internal

Read ByteString 
Instance details

Defined in Data.ByteString.Internal

Show ByteString 
Instance details

Defined in Data.ByteString.Internal

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

NFData ByteString 
Instance details

Defined in Data.ByteString.Internal

Methods

rnf :: ByteString -> () #

Hashable ByteString 
Instance details

Defined in Data.Hashable.Class

Chunk ByteString 
Instance details

Defined in Data.Attoparsec.Internal.Types

Associated Types

type ChunkElem ByteString #

FromBuilder ByteString 
Instance details

Defined in Fmt.Internal.Core

Ixed ByteString 
Instance details

Defined in Control.Lens.At

Stream ByteString 
Instance details

Defined in Text.Megaparsec.Stream

Associated Types

type Token ByteString #

type Tokens ByteString #

TypeHasDoc ByteString 
Instance details

Defined in Michelson.Typed.Haskell.Doc

IsoValue ByteString 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT ByteString :: T #

One ByteString 
Instance details

Defined in Universum.Container.Class

Associated Types

type OneItem ByteString #

Container ByteString 
Instance details

Defined in Universum.Container.Class

Associated Types

type Element ByteString #

Print ByteString 
Instance details

Defined in Universum.Print.Internal

Methods

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

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

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

HasTypeAnn ByteString Source # 
Instance details

Defined in Lorentz.TypeAnns

ConvertUtf8 String ByteString 
Instance details

Defined in Universum.String.Conversion

ConvertUtf8 Text ByteString 
Instance details

Defined in Universum.String.Conversion

ConvertUtf8 Text ByteString 
Instance details

Defined in Universum.String.Conversion

Cons ByteString ByteString Word8 Word8 
Instance details

Defined in Control.Lens.Cons

Snoc ByteString ByteString Word8 Word8 
Instance details

Defined in Control.Lens.Cons

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

Defined in Michelson.Typed.Haskell.Doc

type ToT ByteString 
Instance details

Defined in Michelson.Typed.Haskell.Value

type OneItem ByteString 
Instance details

Defined in Universum.Container.Class

type Element ByteString 
Instance details

Defined in Universum.Container.Class

data Address #

Data type corresponding to address structure in Tezos.

Instances

Instances details
Eq Address 
Instance details

Defined in Tezos.Address

Methods

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

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

Ord Address 
Instance details

Defined in Tezos.Address

Show Address 
Instance details

Defined in Tezos.Address

Generic Address 
Instance details

Defined in Tezos.Address

Associated Types

type Rep Address :: Type -> Type #

Methods

from :: Address -> Rep Address x #

to :: Rep Address x -> Address #

Arbitrary Address 
Instance details

Defined in Tezos.Address

NFData Address 
Instance details

Defined in Tezos.Address

Methods

rnf :: Address -> () #

ToJSON Address 
Instance details

Defined in Tezos.Address

ToJSONKey Address 
Instance details

Defined in Tezos.Address

FromJSON Address 
Instance details

Defined in Tezos.Address

FromJSONKey Address 
Instance details

Defined in Tezos.Address

Buildable Address 
Instance details

Defined in Tezos.Address

Methods

build :: Address -> Builder #

TypeHasDoc Address 
Instance details

Defined in Michelson.Typed.Haskell.Doc

IsoValue Address 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Address :: T #

HasCLReader Address 
Instance details

Defined in Tezos.Address

HasTypeAnn Address Source # 
Instance details

Defined in Lorentz.TypeAnns

ToAddress Address Source # 
Instance details

Defined in Lorentz.Address

FromContractRef cp Address Source # 
Instance details

Defined in Lorentz.Address

ToTAddress cp Address Source # 
Instance details

Defined in Lorentz.Address

CanCastTo Address (TAddress p :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy Address -> Proxy (TAddress p) -> () Source #

CanCastTo (TAddress p :: Type) Address Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (TAddress p) -> Proxy Address -> () Source #

type Rep Address 
Instance details

Defined in Tezos.Address

type Rep Address = D1 ('MetaData "Address" "Tezos.Address" "morley-1.4.0-FPgS4VJ0cLmB07ubDf4i8P" 'False) (C1 ('MetaCons "KeyAddress" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 KeyHash)) :+: C1 ('MetaCons "ContractAddress" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ContractHash)))
type TypeDocFieldDescriptions Address 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type ToT Address 
Instance details

Defined in Michelson.Typed.Haskell.Value

data EpAddress #

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

Constructors

EpAddress 

Fields

Instances

Instances details
Eq EpAddress 
Instance details

Defined in Michelson.Typed.EntryPoints

Ord EpAddress 
Instance details

Defined in Michelson.Typed.EntryPoints

Show EpAddress 
Instance details

Defined in Michelson.Typed.EntryPoints

Generic EpAddress 
Instance details

Defined in Michelson.Typed.EntryPoints

Associated Types

type Rep EpAddress :: Type -> Type #

Arbitrary FieldAnn => Arbitrary EpAddress 
Instance details

Defined in Michelson.Typed.EntryPoints

NFData EpAddress 
Instance details

Defined in Michelson.Typed.EntryPoints

Methods

rnf :: EpAddress -> () #

Buildable EpAddress 
Instance details

Defined in Michelson.Typed.EntryPoints

Methods

build :: EpAddress -> Builder #

TypeHasDoc EpAddress 
Instance details

Defined in Michelson.Typed.Haskell.Doc

IsoValue EpAddress 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT EpAddress :: T #

HasTypeAnn EpAddress Source # 
Instance details

Defined in Lorentz.TypeAnns

ToAddress EpAddress Source # 
Instance details

Defined in Lorentz.Address

FromContractRef cp EpAddress Source # 
Instance details

Defined in Lorentz.Address

CanCastTo (FutureContract p :: Type) EpAddress Source # 
Instance details

Defined in Lorentz.Coercions

type Rep EpAddress 
Instance details

Defined in Michelson.Typed.EntryPoints

type Rep EpAddress = D1 ('MetaData "EpAddress" "Michelson.Typed.EntryPoints" "morley-1.4.0-FPgS4VJ0cLmB07ubDf4i8P" 'False) (C1 ('MetaCons "EpAddress" 'PrefixI 'True) (S1 ('MetaSel ('Just "eaAddress") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Address) :*: S1 ('MetaSel ('Just "eaEntryPoint") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 EpName)))
type TypeDocFieldDescriptions EpAddress 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type ToT EpAddress 
Instance details

Defined in Michelson.Typed.Haskell.Value

data Mutez #

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

Instances

Instances details
Bounded Mutez 
Instance details

Defined in Tezos.Core

Enum Mutez 
Instance details

Defined in Tezos.Core

Eq Mutez 
Instance details

Defined in Tezos.Core

Methods

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

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

Data Mutez 
Instance details

Defined in Tezos.Core

Methods

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

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

toConstr :: Mutez -> Constr #

dataTypeOf :: Mutez -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Mutez 
Instance details

Defined in Tezos.Core

Methods

compare :: Mutez -> Mutez -> Ordering #

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

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

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

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

max :: Mutez -> Mutez -> Mutez #

min :: Mutez -> Mutez -> Mutez #

Show Mutez 
Instance details

Defined in Tezos.Core

Methods

showsPrec :: Int -> Mutez -> ShowS #

show :: Mutez -> String #

showList :: [Mutez] -> ShowS #

Generic Mutez 
Instance details

Defined in Tezos.Core

Associated Types

type Rep Mutez :: Type -> Type #

Methods

from :: Mutez -> Rep Mutez x #

to :: Rep Mutez x -> Mutez #

NFData Mutez 
Instance details

Defined in Tezos.Core

Methods

rnf :: Mutez -> () #

ToJSON Mutez 
Instance details

Defined in Tezos.Core

FromJSON Mutez 
Instance details

Defined in Tezos.Core

Buildable Mutez 
Instance details

Defined in Tezos.Core

Methods

build :: Mutez -> Builder #

TypeHasDoc Mutez 
Instance details

Defined in Michelson.Typed.Haskell.Doc

IsoValue Mutez 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Mutez :: T #

HasCLReader Mutez 
Instance details

Defined in Tezos.Core

HasTypeAnn Mutez Source # 
Instance details

Defined in Lorentz.TypeAnns

EDivOpHs Mutez Natural Source # 
Instance details

Defined in Lorentz.Polymorphic

EDivOpHs Mutez Mutez Source # 
Instance details

Defined in Lorentz.Polymorphic

ArithOpHs Add Mutez Mutez Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Mutez Mutez Source #

ArithOpHs Sub Mutez Mutez Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Sub Mutez Mutez Source #

ArithOpHs Mul Natural Mutez Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Natural Mutez Source #

ArithOpHs Mul Mutez Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Mul Mutez Natural Source #

type Rep Mutez 
Instance details

Defined in Tezos.Core

type Rep Mutez = D1 ('MetaData "Mutez" "Tezos.Core" "morley-1.4.0-FPgS4VJ0cLmB07ubDf4i8P" 'True) (C1 ('MetaCons "Mutez" 'PrefixI 'True) (S1 ('MetaSel ('Just "unMutez") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)))
type TypeDocFieldDescriptions Mutez 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type ToT Mutez 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT Mutez = 'TMutez
type EDivOpResHs Mutez Natural Source # 
Instance details

Defined in Lorentz.Polymorphic

type EDivOpResHs Mutez Mutez Source # 
Instance details

Defined in Lorentz.Polymorphic

type EModOpResHs Mutez Natural Source # 
Instance details

Defined in Lorentz.Polymorphic

type EModOpResHs Mutez Mutez Source # 
Instance details

Defined in Lorentz.Polymorphic

type ArithResHs Add Mutez Mutez Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Sub 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

data Timestamp #

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

Instances

Instances details
Eq Timestamp 
Instance details

Defined in Tezos.Core

Data Timestamp 
Instance details

Defined in Tezos.Core

Methods

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

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

toConstr :: Timestamp -> Constr #

dataTypeOf :: Timestamp -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Timestamp 
Instance details

Defined in Tezos.Core

Show Timestamp 
Instance details

Defined in Tezos.Core

Generic Timestamp 
Instance details

Defined in Tezos.Core

Associated Types

type Rep Timestamp :: Type -> Type #

NFData Timestamp 
Instance details

Defined in Tezos.Core

Methods

rnf :: Timestamp -> () #

ToJSON Timestamp 
Instance details

Defined in Tezos.Core

FromJSON Timestamp 
Instance details

Defined in Tezos.Core

Buildable Timestamp 
Instance details

Defined in Tezos.Core

Methods

build :: Timestamp -> Builder #

TypeHasDoc Timestamp 
Instance details

Defined in Michelson.Typed.Haskell.Doc

IsoValue Timestamp 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Timestamp :: T #

HasTypeAnn Timestamp Source # 
Instance details

Defined in Lorentz.TypeAnns

ArithOpHs Add Integer Timestamp Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Integer Timestamp Source #

ArithOpHs Add Timestamp Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Add Timestamp Integer Source #

ArithOpHs Sub Timestamp Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Sub Timestamp Integer Source #

ArithOpHs Sub Timestamp Timestamp Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type ArithResHs Sub Timestamp Timestamp Source #

type Rep Timestamp 
Instance details

Defined in Tezos.Core

type Rep Timestamp = D1 ('MetaData "Timestamp" "Tezos.Core" "morley-1.4.0-FPgS4VJ0cLmB07ubDf4i8P" 'True) (C1 ('MetaCons "Timestamp" 'PrefixI 'True) (S1 ('MetaSel ('Just "unTimestamp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 POSIXTime)))
type TypeDocFieldDescriptions Timestamp 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type ToT Timestamp 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ArithResHs Add Integer Timestamp Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Add Timestamp Integer Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Sub Timestamp Integer Source # 
Instance details

Defined in Lorentz.Arith

type ArithResHs Sub Timestamp Timestamp Source # 
Instance details

Defined in Lorentz.Arith

data ChainId #

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

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

Instances

Instances details
Eq ChainId 
Instance details

Defined in Tezos.Core

Methods

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

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

Show ChainId 
Instance details

Defined in Tezos.Core

Generic ChainId 
Instance details

Defined in Tezos.Core

Associated Types

type Rep ChainId :: Type -> Type #

Methods

from :: ChainId -> Rep ChainId x #

to :: Rep ChainId x -> ChainId #

Arbitrary ChainId 
Instance details

Defined in Tezos.Core

NFData ChainId 
Instance details

Defined in Tezos.Core

Methods

rnf :: ChainId -> () #

ToJSON ChainId 
Instance details

Defined in Tezos.Core

FromJSON ChainId 
Instance details

Defined in Tezos.Core

Buildable ChainId 
Instance details

Defined in Tezos.Core

Methods

build :: ChainId -> Builder #

IsoValue ChainId 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT ChainId :: T #

type Rep ChainId 
Instance details

Defined in Tezos.Core

type Rep ChainId = D1 ('MetaData "ChainId" "Tezos.Core" "morley-1.4.0-FPgS4VJ0cLmB07ubDf4i8P" 'True) (C1 ('MetaCons "ChainIdUnsafe" 'PrefixI 'True) (S1 ('MetaSel ('Just "unChainId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))
type ToT ChainId 
Instance details

Defined in Michelson.Typed.Haskell.Value

data KeyHash #

Blake2b_160 hash of a public key.

Instances

Instances details
Eq KeyHash 
Instance details

Defined in Tezos.Crypto

Methods

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

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

Ord KeyHash 
Instance details

Defined in Tezos.Crypto

Show KeyHash 
Instance details

Defined in Tezos.Crypto

Generic KeyHash 
Instance details

Defined in Tezos.Crypto

Associated Types

type Rep KeyHash :: Type -> Type #

Methods

from :: KeyHash -> Rep KeyHash x #

to :: Rep KeyHash x -> KeyHash #

Arbitrary KeyHash 
Instance details

Defined in Tezos.Crypto

NFData KeyHash 
Instance details

Defined in Tezos.Crypto

Methods

rnf :: KeyHash -> () #

ToJSON KeyHash 
Instance details

Defined in Tezos.Crypto

FromJSON KeyHash 
Instance details

Defined in Tezos.Crypto

Buildable KeyHash 
Instance details

Defined in Tezos.Crypto

Methods

build :: KeyHash -> Builder #

TypeHasDoc KeyHash 
Instance details

Defined in Michelson.Typed.Haskell.Doc

IsoValue KeyHash 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT KeyHash :: T #

HasCLReader KeyHash 
Instance details

Defined in Tezos.Crypto

HasTypeAnn KeyHash Source # 
Instance details

Defined in Lorentz.TypeAnns

type Rep KeyHash 
Instance details

Defined in Tezos.Crypto

type Rep KeyHash = D1 ('MetaData "KeyHash" "Tezos.Crypto" "morley-1.4.0-FPgS4VJ0cLmB07ubDf4i8P" 'False) (C1 ('MetaCons "KeyHash" 'PrefixI 'True) (S1 ('MetaSel ('Just "khTag") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 KeyHashTag) :*: S1 ('MetaSel ('Just "khBytes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ByteString)))
type TypeDocFieldDescriptions KeyHash 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type ToT KeyHash 
Instance details

Defined in Michelson.Typed.Haskell.Value

data PublicKey #

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

Instances

Instances details
Eq PublicKey 
Instance details

Defined in Tezos.Crypto

Show PublicKey 
Instance details

Defined in Tezos.Crypto

Generic PublicKey 
Instance details

Defined in Tezos.Crypto

Associated Types

type Rep PublicKey :: Type -> Type #

Arbitrary PublicKey 
Instance details

Defined in Tezos.Crypto

NFData PublicKey 
Instance details

Defined in Tezos.Crypto

Methods

rnf :: PublicKey -> () #

ToJSON PublicKey 
Instance details

Defined in Tezos.Crypto

FromJSON PublicKey 
Instance details

Defined in Tezos.Crypto

Buildable PublicKey 
Instance details

Defined in Tezos.Crypto

Methods

build :: PublicKey -> Builder #

TypeHasDoc PublicKey 
Instance details

Defined in Michelson.Typed.Haskell.Doc

IsoValue PublicKey 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT PublicKey :: T #

HasTypeAnn PublicKey Source # 
Instance details

Defined in Lorentz.TypeAnns

type Rep PublicKey 
Instance details

Defined in Tezos.Crypto

type TypeDocFieldDescriptions PublicKey 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type ToT PublicKey 
Instance details

Defined in Michelson.Typed.Haskell.Value

data Signature #

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

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

Instances

Instances details
Eq Signature 
Instance details

Defined in Tezos.Crypto

Show Signature 
Instance details

Defined in Tezos.Crypto

Generic Signature 
Instance details

Defined in Tezos.Crypto

Associated Types

type Rep Signature :: Type -> Type #

Arbitrary Signature 
Instance details

Defined in Tezos.Crypto

NFData Signature 
Instance details

Defined in Tezos.Crypto

Methods

rnf :: Signature -> () #

ToJSON Signature 
Instance details

Defined in Tezos.Crypto

FromJSON Signature 
Instance details

Defined in Tezos.Crypto

Buildable Signature 
Instance details

Defined in Tezos.Crypto

Methods

build :: Signature -> Builder #

TypeHasDoc Signature 
Instance details

Defined in Michelson.Typed.Haskell.Doc

IsoValue Signature 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT Signature :: T #

HasTypeAnn Signature Source # 
Instance details

Defined in Lorentz.TypeAnns

type Rep Signature 
Instance details

Defined in Tezos.Crypto

type TypeDocFieldDescriptions Signature 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type ToT Signature 
Instance details

Defined in Michelson.Typed.Haskell.Value

data Set a #

A set of values a.

Instances

Instances details
Foldable Set

Folds in order of increasing key.

Instance details

Defined in Data.Set.Internal

Methods

fold :: Monoid m => Set m -> m #

foldMap :: Monoid m => (a -> m) -> Set a -> m #

foldMap' :: Monoid m => (a -> m) -> Set a -> m #

foldr :: (a -> b -> b) -> b -> Set a -> b #

foldr' :: (a -> b -> b) -> b -> Set a -> b #

foldl :: (b -> a -> b) -> b -> Set a -> b #

foldl' :: (b -> a -> b) -> b -> Set a -> b #

foldr1 :: (a -> a -> a) -> Set a -> a #

foldl1 :: (a -> a -> a) -> Set a -> a #

toList :: Set a -> [a] #

null :: Set a -> Bool #

length :: Set a -> Int #

elem :: Eq a => a -> Set a -> Bool #

maximum :: Ord a => Set a -> a #

minimum :: Ord a => Set a -> a #

sum :: Num a => Set a -> a #

product :: Num a => Set a -> a #

ToJSON1 Set 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Set a -> Value #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Set a] -> Value #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Set a -> Encoding #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Set a] -> Encoding #

Eq1 Set

Since: containers-0.5.9

Instance details

Defined in Data.Set.Internal

Methods

liftEq :: (a -> b -> Bool) -> Set a -> Set b -> Bool #

Ord1 Set

Since: containers-0.5.9

Instance details

Defined in Data.Set.Internal

Methods

liftCompare :: (a -> b -> Ordering) -> Set a -> Set b -> Ordering #

Show1 Set

Since: containers-0.5.9

Instance details

Defined in Data.Set.Internal

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Set a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Set a] -> ShowS #

Ord a => IsList (Set a)

Since: containers-0.5.6.2

Instance details

Defined in Data.Set.Internal

Associated Types

type Item (Set a) #

Methods

fromList :: [Item (Set a)] -> Set a #

fromListN :: Int -> [Item (Set a)] -> Set a #

toList :: Set a -> [Item (Set a)] #

Eq a => Eq (Set a) 
Instance details

Defined in Data.Set.Internal

Methods

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

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

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

Defined in Data.Set.Internal

Methods

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

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

toConstr :: Set a -> Constr #

dataTypeOf :: Set a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord a => Ord (Set a) 
Instance details

Defined in Data.Set.Internal

Methods

compare :: Set a -> Set a -> Ordering #

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

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

(>) :: Set a -> Set a -> Bool #

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

max :: Set a -> Set a -> Set a #

min :: Set a -> Set a -> Set a #

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

Defined in Data.Set.Internal

Show a => Show (Set a) 
Instance details

Defined in Data.Set.Internal

Methods

showsPrec :: Int -> Set a -> ShowS #

show :: Set a -> String #

showList :: [Set a] -> ShowS #

Ord a => Semigroup (Set a)

Since: containers-0.5.7

Instance details

Defined in Data.Set.Internal

Methods

(<>) :: Set a -> Set a -> Set a #

sconcat :: NonEmpty (Set a) -> Set a #

stimes :: Integral b => b -> Set a -> Set a #

Ord a => Monoid (Set a) 
Instance details

Defined in Data.Set.Internal

Methods

mempty :: Set a #

mappend :: Set a -> Set a -> Set a #

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

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

NFData a => NFData (Set a) 
Instance details

Defined in Data.Set.Internal

Methods

rnf :: Set a -> () #

ToJSON a => ToJSON (Set a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Set a -> Value #

toEncoding :: Set a -> Encoding #

toJSONList :: [Set a] -> Value #

toEncodingList :: [Set a] -> Encoding #

Ord a => Contains (Set a) 
Instance details

Defined in Control.Lens.At

Methods

contains :: Index (Set a) -> Lens' (Set a) Bool #

Ord k => Ixed (Set k) 
Instance details

Defined in Control.Lens.At

Methods

ix :: Index (Set k) -> Traversal' (Set k) (IxValue (Set k)) #

Ord k => At (Set k) 
Instance details

Defined in Control.Lens.At

Methods

at :: Index (Set k) -> Lens' (Set k) (Maybe (IxValue (Set k))) #

Ord a => Wrapped (Set a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Set a) #

Methods

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

PolyCTypeHasDocC '[a] => TypeHasDoc (Set a) 
Instance details

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions (Set a) :: FieldDescriptions #

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

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (Set c) :: T #

Methods

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

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

One (Set v) 
Instance details

Defined in Universum.Container.Class

Associated Types

type OneItem (Set v) #

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

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

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

Defined in Lorentz.Polymorphic

Associated Types

type UpdOpKeyHs (Set a) Source #

type UpdOpParamsHs (Set a) Source #

SizeOpHs (Set a) Source # 
Instance details

Defined in Lorentz.Polymorphic

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

Defined in Lorentz.Polymorphic

Associated Types

type IterOpElHs (Set e) Source #

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

Defined in Lorentz.Polymorphic

Associated Types

type MemOpKeyHs (Set e) Source #

KnownIsoT v => HasTypeAnn (Set v) Source # 
Instance details

Defined in Lorentz.TypeAnns

Methods

getTypeAnn :: Notes (ToT (Set v)) Source #

(t ~ Set a', Ord a) => Rewrapped (Set a) t

Use wrapping fromList. unwrapping returns a sorted list.

Instance details

Defined in Control.Lens.Wrapped

CanCastTo k1 k2 => CanCastTo (Set k1 :: Type) (Set k2 :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (Set k1) -> Proxy (Set k2) -> () Source #

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 TypeDocFieldDescriptions (Set a) 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type ToT (Set c) 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT (Set c) = 'TSet (ToT c)
type 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 UpdOpKeyHs (Set a) Source # 
Instance details

Defined in Lorentz.Polymorphic

type UpdOpKeyHs (Set a) = a
type UpdOpParamsHs (Set a) Source # 
Instance details

Defined in Lorentz.Polymorphic

type IterOpElHs (Set e) Source # 
Instance details

Defined in Lorentz.Polymorphic

type IterOpElHs (Set e) = e
type MemOpKeyHs (Set e) Source # 
Instance details

Defined in Lorentz.Polymorphic

type MemOpKeyHs (Set e) = e

data Map k a #

A Map from keys k to values a.

The Semigroup operation for Map is union, which prefers values from the left operand. If m1 maps a key k to a value a1, and m2 maps the same key to a different value a2, then their union m1 <> m2 maps k to a1.

Instances

Instances details
Eq2 Map

Since: containers-0.5.9

Instance details

Defined in Data.Map.Internal

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> Map a c -> Map b d -> Bool #

Ord2 Map

Since: containers-0.5.9

Instance details

Defined in Data.Map.Internal

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> Map a c -> Map b d -> Ordering #

Show2 Map

Since: containers-0.5.9

Instance details

Defined in Data.Map.Internal

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> Map a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [Map a b] -> ShowS #

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

Defined in Control.Lens.Traversal

Methods

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

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

Defined in Control.Lens.Traversal

Methods

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

Functor (Map k) 
Instance details

Defined in Data.Map.Internal

Methods

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

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

Foldable (Map k)

Folds in order of increasing key.

Instance details

Defined in Data.Map.Internal

Methods

fold :: Monoid m => Map k m -> m #

foldMap :: Monoid m => (a -> m) -> Map k a -> m #

foldMap' :: Monoid m => (a -> m) -> Map k a -> m #

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

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

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

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

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

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

toList :: Map k a -> [a] #

null :: Map k a -> Bool #

length :: Map k a -> Int #

elem :: Eq a => a -> Map k a -> Bool #

maximum :: Ord a => Map k a -> a #

minimum :: Ord a => Map k a -> a #

sum :: Num a => Map k a -> a #

product :: Num a => Map k a -> a #

Traversable (Map k)

Traverses in order of increasing key.

Instance details

Defined in Data.Map.Internal

Methods

traverse :: Applicative f => (a -> f b) -> Map k a -> f (Map k b) #

sequenceA :: Applicative f => Map k (f a) -> f (Map k a) #

mapM :: Monad m => (a -> m b) -> Map k a -> m (Map k b) #

sequence :: Monad m => Map k (m a) -> m (Map k a) #

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

Eq k => Eq1 (Map k)

Since: containers-0.5.9

Instance details

Defined in Data.Map.Internal

Methods

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

Ord k => Ord1 (Map k)

Since: containers-0.5.9

Instance details

Defined in Data.Map.Internal

Methods

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

(Ord k, Read k) => Read1 (Map k)

Since: containers-0.5.9

Instance details

Defined in Data.Map.Internal

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Map k a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Map k a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Map k a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Map k a] #

Show k => Show1 (Map k)

Since: containers-0.5.9

Instance details

Defined in Data.Map.Internal

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Map k a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Map k a] -> ShowS #

Ord k => Apply (Map k)

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

Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

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

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

Ord k => Bind (Map k)

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

Instance details

Defined in Data.Functor.Bind.Class

Methods

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

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

(CanCastTo k1 k2, CanCastTo v1 v2) => CanCastTo (Map k1 v1 :: Type) (Map k2 v2 :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (Map k1 v1) -> Proxy (Map k2 v2) -> () Source #

Ord k => IsList (Map k v)

Since: containers-0.5.6.2

Instance details

Defined in Data.Map.Internal

Associated Types

type Item (Map k v) #

Methods

fromList :: [Item (Map k v)] -> Map k v #

fromListN :: Int -> [Item (Map k v)] -> Map k v #

toList :: Map k v -> [Item (Map k v)] #

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

Defined in Data.Map.Internal

Methods

(==) :: Map k a -> Map k a -> Bool #

(/=) :: Map k a -> Map k a -> Bool #

(Data k, Data a, Ord k) => Data (Map k a) 
Instance details

Defined in Data.Map.Internal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Map k a -> c (Map k a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Map k a) #

toConstr :: Map k a -> Constr #

dataTypeOf :: Map k a -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> Map k a -> Map k a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Map k a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Map k a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Map k a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Map k a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Map k a -> m (Map k a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Map k a -> m (Map k a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Map k a -> m (Map k a) #

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

Defined in Data.Map.Internal

Methods

compare :: Map k v -> Map k v -> Ordering #

(<) :: Map k v -> Map k v -> Bool #

(<=) :: Map k v -> Map k v -> Bool #

(>) :: Map k v -> Map k v -> Bool #

(>=) :: Map k v -> Map k v -> Bool #

max :: Map k v -> Map k v -> Map k v #

min :: Map k v -> Map k v -> Map k v #

(Ord k, Read k, Read e) => Read (Map k e) 
Instance details

Defined in Data.Map.Internal

Methods

readsPrec :: Int -> ReadS (Map k e) #

readList :: ReadS [Map k e] #

readPrec :: ReadPrec (Map k e) #

readListPrec :: ReadPrec [Map k e] #

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

Defined in Data.Map.Internal

Methods

showsPrec :: Int -> Map k a -> ShowS #

show :: Map k a -> String #

showList :: [Map k a] -> ShowS #

Ord k => Semigroup (Map k v) 
Instance details

Defined in Data.Map.Internal

Methods

(<>) :: Map k v -> Map k v -> Map k v #

sconcat :: NonEmpty (Map k v) -> Map k v #

stimes :: Integral b => b -> Map k v -> Map k v #

Ord k => Monoid (Map k v) 
Instance details

Defined in Data.Map.Internal

Methods

mempty :: Map k v #

mappend :: Map k v -> Map k v -> Map k v #

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

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

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

Defined in Data.Map.Internal

Methods

rnf :: Map k a -> () #

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

Ord k => Ixed (Map k a) 
Instance details

Defined in Control.Lens.At

Methods

ix :: Index (Map k a) -> Traversal' (Map k a) (IxValue (Map k a)) #

Ord k => At (Map k a) 
Instance details

Defined in Control.Lens.At

Methods

at :: Index (Map k a) -> Lens' (Map k a) (Maybe (IxValue (Map k a))) #

Ord k => Wrapped (Map k a) 
Instance details

Defined in Control.Lens.Wrapped

Associated Types

type Unwrapped (Map k a) #

Methods

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

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

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions (Map k v) :: FieldDescriptions #

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

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (Map k v) :: T #

Methods

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

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

One (Map k v) 
Instance details

Defined in Universum.Container.Class

Associated Types

type OneItem (Map k v) #

Methods

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

Container (Map k v) 
Instance details

Defined in Universum.Container.Class

Associated Types

type Element (Map k v) #

Methods

toList :: Map k v -> [Element (Map k v)] #

null :: Map k v -> Bool #

foldr :: (Element (Map k v) -> b -> b) -> b -> Map k v -> b #

foldl :: (b -> Element (Map k v) -> b) -> b -> Map k v -> b #

foldl' :: (b -> Element (Map k v) -> b) -> b -> Map k v -> b #

length :: Map k v -> Int #

elem :: Element (Map k v) -> Map k v -> Bool #

maximum :: Map k v -> Element (Map k v) #

minimum :: Map k v -> Element (Map k v) #

foldMap :: Monoid m => (Element (Map k v) -> m) -> Map k v -> m #

fold :: Map k v -> Element (Map k v) #

foldr' :: (Element (Map k v) -> b -> b) -> b -> Map k v -> b #

foldr1 :: (Element (Map k v) -> Element (Map k v) -> Element (Map k v)) -> Map k v -> Element (Map k v) #

foldl1 :: (Element (Map k v) -> Element (Map k v) -> Element (Map k v)) -> Map k v -> Element (Map k v) #

notElem :: Element (Map k v) -> Map k v -> Bool #

all :: (Element (Map k v) -> Bool) -> Map k v -> Bool #

any :: (Element (Map k v) -> Bool) -> Map k v -> Bool #

and :: Map k v -> Bool #

or :: Map k v -> Bool #

find :: (Element (Map k v) -> Bool) -> Map k v -> Maybe (Element (Map k v)) #

safeHead :: Map k v -> Maybe (Element (Map k v)) #

ToPairs (Map k v) 
Instance details

Defined in Universum.Container.Class

Associated Types

type Key (Map k v) #

type Val (Map k v) #

Methods

toPairs :: Map k v -> [(Key (Map k v), Val (Map k v))] #

keys :: Map k v -> [Key (Map k v)] #

elems :: Map k v -> [Val (Map k v)] #

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

Defined in Lorentz.Polymorphic

Associated Types

type GetOpKeyHs (Map k v) Source #

type GetOpValHs (Map k v) Source #

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

Defined in Lorentz.Polymorphic

Associated Types

type UpdOpKeyHs (Map k v) Source #

type UpdOpParamsHs (Map k v) Source #

SizeOpHs (Map k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

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

Defined in Lorentz.Polymorphic

Associated Types

type IterOpElHs (Map k v) Source #

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

Defined in Lorentz.Polymorphic

Associated Types

type MapOpInpHs (Map k v) Source #

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

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

Defined in Lorentz.Polymorphic

Associated Types

type MemOpKeyHs (Map k v) Source #

(HasTypeAnn k, HasTypeAnn v) => HasTypeAnn (Map k v) Source # 
Instance details

Defined in Lorentz.TypeAnns

Methods

getTypeAnn :: Notes (ToT (Map k v)) Source #

(t ~ Map k' a', Ord k) => Rewrapped (Map k a) t

Use wrapping fromList. unwrapping returns a sorted list.

Instance details

Defined in Control.Lens.Wrapped

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

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

Instance details

Defined in Lorentz.StoreClass

Methods

storeSubmapOps :: StoreSubmapOps (Map key' value') name key value Source #

type Item (Map k v) 
Instance details

Defined in Data.Map.Internal

type Item (Map k v) = (k, v)
type Index (Map k a) 
Instance details

Defined in Control.Lens.At

type Index (Map k a) = k
type IxValue (Map k a) 
Instance details

Defined in Control.Lens.At

type IxValue (Map k a) = a
type Unwrapped (Map k a) 
Instance details

Defined in Control.Lens.Wrapped

type Unwrapped (Map k a) = [(k, a)]
type TypeDocFieldDescriptions (Map k v) 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type TypeDocFieldDescriptions (Map k v) = '[] :: [(Symbol, (Maybe Symbol, [(Symbol, Symbol)]))]
type ToT (Map k v) 
Instance details

Defined in Michelson.Typed.Haskell.Value

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

Defined in Lorentz.Polymorphic

type GetOpKeyHs (Map k v) = k
type GetOpValHs (Map k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

type GetOpValHs (Map k v) = v
type UpdOpKeyHs (Map k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

type UpdOpKeyHs (Map k v) = k
type UpdOpParamsHs (Map k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

type UpdOpParamsHs (Map k v) = Maybe v
type IterOpElHs (Map k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

type IterOpElHs (Map k v) = (k, v)
type MapOpInpHs (Map k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

type MapOpInpHs (Map k v) = (k, v)
type MapOpResHs (Map k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

type MapOpResHs (Map k v) = Map k
type MemOpKeyHs (Map k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

type MemOpKeyHs (Map k v) = k

newtype BigMap k v #

Constructors

BigMap 

Fields

Instances

Instances details
(CanCastTo k1 k2, CanCastTo v1 v2) => CanCastTo (BigMap k1 v1 :: Type) (BigMap k2 v2 :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (BigMap k1 v1) -> Proxy (BigMap k2 v2) -> () Source #

(Eq k, Eq v) => Eq (BigMap k v) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Methods

(==) :: BigMap k v -> BigMap k v -> Bool #

(/=) :: BigMap k v -> BigMap k v -> Bool #

(Show k, Show v) => Show (BigMap k v) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Methods

showsPrec :: Int -> BigMap k v -> ShowS #

show :: BigMap k v -> String #

showList :: [BigMap k v] -> ShowS #

Ord k => Semigroup (BigMap k v) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Methods

(<>) :: BigMap k v -> BigMap k v -> BigMap k v #

sconcat :: NonEmpty (BigMap k v) -> BigMap k v #

stimes :: Integral b => b -> BigMap k v -> BigMap k v #

Ord k => Monoid (BigMap k v) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Methods

mempty :: BigMap k v #

mappend :: BigMap k v -> BigMap k v -> BigMap k v #

mconcat :: [BigMap k v] -> BigMap k v #

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

Defined in Michelson.Typed.Haskell.Value

Methods

arbitrary :: Gen (BigMap k v) #

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

Default (BigMap k v) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Methods

def :: BigMap k v #

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

Defined in Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions (BigMap k v) :: FieldDescriptions #

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

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (BigMap k v) :: T #

Methods

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

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

NiceComparable k => GetOpHs (BigMap k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

Associated Types

type GetOpKeyHs (BigMap k v) Source #

type GetOpValHs (BigMap k v) Source #

NiceComparable k => UpdOpHs (BigMap k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

Associated Types

type UpdOpKeyHs (BigMap k v) Source #

type UpdOpParamsHs (BigMap k v) Source #

NiceComparable k => MemOpHs (BigMap k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

Associated Types

type MemOpKeyHs (BigMap k v) Source #

(HasTypeAnn k, HasTypeAnn v) => HasTypeAnn (BigMap k v) Source # 
Instance details

Defined in Lorentz.TypeAnns

Methods

getTypeAnn :: Notes (ToT (BigMap k v)) Source #

(key ~ key', value ~ value', NiceComparable key) => StoreHasSubmap (BigMap key' value') name key value Source #

BigMap can be used as standalone key-value storage, name of submap is not accounted in this case.

Instance details

Defined in Lorentz.StoreClass

Methods

storeSubmapOps :: StoreSubmapOps (BigMap key' value') name key value Source #

type TypeDocFieldDescriptions (BigMap k v) 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type ToT (BigMap k v) 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT (BigMap k v) = 'TBigMap (ToT k) (ToT v)
type GetOpKeyHs (BigMap k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

type GetOpKeyHs (BigMap k v) = k
type GetOpValHs (BigMap k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

type GetOpValHs (BigMap k v) = v
type UpdOpKeyHs (BigMap k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

type UpdOpKeyHs (BigMap k v) = k
type UpdOpParamsHs (BigMap k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

type UpdOpParamsHs (BigMap k v) = Maybe v
type MemOpKeyHs (BigMap k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

type MemOpKeyHs (BigMap k v) = k

data Maybe a #

The Maybe type encapsulates an optional value. A value of type Maybe a either contains a value of type a (represented as Just a), or it is empty (represented as Nothing). Using Maybe is a good way to deal with errors or exceptional cases without resorting to drastic measures such as error.

The Maybe type is also a monad. It is a simple kind of error monad, where all errors are represented by Nothing. A richer error monad can be built using the Either type.

Constructors

Nothing 
Just a 

Instances

Instances details
Monad Maybe

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

(>>=) :: Maybe a -> (a -> Maybe b) -> Maybe b #

(>>) :: Maybe a -> Maybe b -> Maybe b #

return :: a -> Maybe a #

Functor Maybe

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

fmap :: (a -> b) -> Maybe a -> Maybe b #

(<$) :: a -> Maybe b -> Maybe a #

MonadFail Maybe

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.Fail

Methods

fail :: String -> Maybe a #

Applicative Maybe

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

pure :: a -> Maybe a #

(<*>) :: Maybe (a -> b) -> Maybe a -> Maybe b #

liftA2 :: (a -> b -> c) -> Maybe a -> Maybe b -> Maybe c #

(*>) :: Maybe a -> Maybe b -> Maybe b #

(<*) :: Maybe a -> Maybe b -> Maybe a #

Foldable Maybe

Since: base-2.1

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => Maybe m -> m #

foldMap :: Monoid m => (a -> m) -> Maybe a -> m #

foldMap' :: Monoid m => (a -> m) -> Maybe a -> m #

foldr :: (a -> b -> b) -> b -> Maybe a -> b #

foldr' :: (a -> b -> b) -> b -> Maybe a -> b #

foldl :: (b -> a -> b) -> b -> Maybe a -> b #

foldl' :: (b -> a -> b) -> b -> Maybe a -> b #

foldr1 :: (a -> a -> a) -> Maybe a -> a #

foldl1 :: (a -> a -> a) -> Maybe a -> a #

toList :: Maybe a -> [a] #

null :: Maybe a -> Bool #

length :: Maybe a -> Int #

elem :: Eq a => a -> Maybe a -> Bool #

maximum :: Ord a => Maybe a -> a #

minimum :: Ord a => Maybe a -> a #

sum :: Num a => Maybe a -> a #

product :: Num a => Maybe a -> a #

Traversable Maybe

Since: base-2.1

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Maybe a -> f (Maybe b) #

sequenceA :: Applicative f => Maybe (f a) -> f (Maybe a) #

mapM :: Monad m => (a -> m b) -> Maybe a -> m (Maybe b) #

sequence :: Monad m => Maybe (m a) -> m (Maybe a) #

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 #

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 #

Methods

mFail :: Failure Maybe -> Maybe () #

MonadThrow Maybe 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> Maybe a #

NFData1 Maybe

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> 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 #

KnownNamedFunctor Maybe 
Instance details

Defined in Util.Named

Methods

namedL :: forall (name :: Symbol) a. Label name -> Iso' (NamedF Maybe a name) (ApplyNamedFunctor Maybe a) #

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 arg0 arg1 :: f0 (t0 b0) #

type SequenceA arg0 :: f0 (t0 a0) #

type MapM arg0 arg1 :: m0 (t0 b0) #

type Sequence arg0 :: m0 (t0 a0) #

STraversable Maybe 
Instance details

Defined in Data.Singletons.Prelude.Traversable

Methods

sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: Maybe a). SApplicative f => Sing t1 -> Sing t2 -> Sing (Apply (Apply TraverseSym0 t1) t2) #

sSequenceA :: forall (f :: Type -> Type) a (t :: Maybe (f a)). SApplicative f => Sing t -> Sing (Apply SequenceASym0 t) #

sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: Maybe a). SMonad m => Sing t1 -> Sing t2 -> Sing (Apply (Apply MapMSym0 t1) t2) #

sSequence :: forall (m :: Type -> Type) a (t :: Maybe (m a)). SMonad m => Sing t -> Sing (Apply SequenceSym0 t) #

PFoldable Maybe 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Associated Types

type Fold arg0 :: m0 #

type FoldMap arg0 arg1 :: m0 #

type Foldr arg0 arg1 arg2 :: b0 #

type Foldr' arg0 arg1 arg2 :: b0 #

type Foldl arg0 arg1 arg2 :: b0 #

type Foldl' arg0 arg1 arg2 :: b0 #

type Foldr1 arg0 arg1 :: a0 #

type Foldl1 arg0 arg1 :: a0 #

type ToList arg0 :: [a0] #

type Null arg0 :: Bool #

type Length arg0 :: Nat #

type Elem arg0 arg1 :: Bool #

type Maximum arg0 :: a0 #

type Minimum arg0 :: a0 #

type Sum arg0 :: a0 #

type Product arg0 :: a0 #

SFoldable Maybe 
Instance details

Defined in Data.Singletons.Prelude.Foldable

Methods

sFold :: forall m (t :: Maybe m). SMonoid m => Sing t -> Sing (Apply FoldSym0 t) #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Maybe a). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply FoldMapSym0 t1) t2) #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Maybe a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply FoldrSym0 t1) t2) t3) #

sFoldr' :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Maybe a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply Foldr'Sym0 t1) t2) t3) #

sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Maybe a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply FoldlSym0 t1) t2) t3) #

sFoldl' :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Maybe a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply Foldl'Sym0 t1) t2) t3) #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Apply (Apply Foldr1Sym0 t1) t2) #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Apply (Apply Foldl1Sym0 t1) t2) #

sToList :: forall a (t :: Maybe a). Sing t -> Sing (Apply ToListSym0 t) #

sNull :: forall a (t :: Maybe a). Sing t -> Sing (Apply NullSym0 t) #

sLength :: forall a (t :: Maybe a). Sing t -> Sing (Apply LengthSym0 t) #

sElem :: forall a (t1 :: a) (t2 :: Maybe a). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply ElemSym0 t1) t2) #

sMaximum :: forall a (t :: Maybe a). SOrd a => Sing t -> Sing (Apply MaximumSym0 t) #

sMinimum :: forall a (t :: Maybe a). SOrd a => Sing t -> Sing (Apply MinimumSym0 t) #

sSum :: forall a (t :: Maybe a). SNum a => Sing t -> Sing (Apply SumSym0 t) #

sProduct :: forall a (t :: Maybe a). SNum a => Sing t -> Sing (Apply ProductSym0 t) #

PMonadFail Maybe 
Instance details

Defined in Data.Singletons.Prelude.Monad.Fail

Associated Types

type Fail arg0 :: m0 a0 #

SMonadFail Maybe 
Instance details

Defined in Data.Singletons.Prelude.Monad.Fail

Methods

sFail :: forall a (t :: [Char]). Sing t -> Sing (Apply FailSym0 t) #

PFunctor Maybe 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

Associated Types

type Fmap arg0 arg1 :: f0 b0 #

type arg0 <$ arg1 :: f0 a0 #

PApplicative Maybe 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

Associated Types

type Pure arg0 :: f0 a0 #

type arg0 <*> arg1 :: f0 b0 #

type LiftA2 arg0 arg1 arg2 :: f0 c0 #

type arg0 *> arg1 :: f0 b0 #

type arg0 <* arg1 :: f0 a0 #

PMonad Maybe 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

Associated Types

type arg0 >>= arg1 :: m0 b0 #

type arg0 >> arg1 :: m0 b0 #

type Return arg0 :: m0 a0 #

PAlternative Maybe 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

Associated Types

type Empty :: f0 a0 #

type arg0 <|> arg1 :: f0 a0 #

PMonadPlus Maybe 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

Associated Types

type Mzero :: m0 a0 #

type Mplus arg0 arg1 :: m0 a0 #

SFunctor Maybe 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Apply (Apply FmapSym0 t1) t2) #

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

SApplicative Maybe 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Apply PureSym0 t) #

(%<*>) :: forall a b (t1 :: Maybe (a ~> b)) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (<*>@#@$) t1) t2) #

sLiftA2 :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: Maybe a) (t3 :: Maybe b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply LiftA2Sym0 t1) t2) t3) #

(%*>) :: forall a b (t1 :: Maybe a) (t2 :: Maybe b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (*>@#@$) t1) t2) #

(%<*) :: forall a b (t1 :: Maybe a) (t2 :: Maybe b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (<*@#@$) t1) t2) #

SMonad Maybe 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

Methods

(%>>=) :: forall a b (t1 :: Maybe a) (t2 :: a ~> Maybe b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (>>=@#@$) t1) t2) #

(%>>) :: forall a b (t1 :: Maybe a) (t2 :: Maybe b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (>>@#@$) t1) t2) #

sReturn :: forall a (t :: a). Sing t -> Sing (Apply ReturnSym0 t) #

SAlternative Maybe 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

Methods

sEmpty :: Sing EmptySym0 #

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

SMonadPlus Maybe 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

Methods

sMzero :: Sing MzeroSym0 #

sMplus :: forall a (t1 :: Maybe a) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Apply (Apply MplusSym0 t1) t2) #

LorentzFunctor Maybe Source # 
Instance details

Defined in Lorentz.Instr

Methods

lmap :: forall b a (s :: [Type]). KnownValue b => ((a ': s) :-> (b ': s)) -> (Maybe a ': s) :-> (Maybe b ': s) Source #

MonadBaseControl Maybe Maybe 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM Maybe a #

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 #

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 :: forall r r'. (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)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (Maybe a) :: Type -> Type #

Methods

from :: Maybe a -> Rep (Maybe a) x #

to :: Rep (Maybe a) x -> Maybe a #

Semigroup a => Semigroup (Maybe a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(<>) :: Maybe a -> Maybe a -> Maybe a #

sconcat :: NonEmpty (Maybe a) -> Maybe a #

stimes :: Integral b => b -> Maybe a -> Maybe a #

Semigroup a => Monoid (Maybe a)

Lift a semigroup into Maybe forming a Monoid according to http://en.wikipedia.org/wiki/Monoid: "Any semigroup S may be turned into a monoid simply by adjoining an element e not in S and defining e*e = e and e*s = s = s*e for all s ∈ S."

Since 4.11.0: constraint on inner a value generalised from Monoid to Semigroup.

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: Maybe a #

mappend :: Maybe a -> Maybe a -> Maybe a #

mconcat :: [Maybe a] -> Maybe a #

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 #

NFData a => NFData (Maybe a) 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Maybe a -> () #

Hashable a => Hashable (Maybe a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Maybe a -> Int #

hash :: Maybe a -> Int #

ToJSON a => ToJSON (Maybe a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

SingKind a => SingKind (Maybe a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type DemoteRep (Maybe a)

Methods

fromSing :: forall (a0 :: Maybe a). Sing a0 -> DemoteRep (Maybe a)

Default (Maybe a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Maybe a #

Buildable a => Buildable (Maybe a) 
Instance details

Defined in Formatting.Buildable

Methods

build :: Maybe a -> Builder #

Ixed (Maybe a) 
Instance details

Defined in Control.Lens.At

Methods

ix :: Index (Maybe a) -> Traversal' (Maybe a) (IxValue (Maybe a)) #

At (Maybe a) 
Instance details

Defined in Control.Lens.At

Methods

at :: Index (Maybe a) -> Lens' (Maybe a) (Maybe (IxValue (Maybe a))) #

PolyTypeHasDocC '[a] => TypeHasDoc (Maybe a) 
Instance details

Defined in Michelson.Typed.Haskell.Doc

IsoValue a => IsoValue (Maybe a) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (Maybe a) :: T #

Methods

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

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

(TypeError (DisallowInstance "Maybe") :: Constraint) => Container (Maybe a) 
Instance details

Defined in Universum.Container.Class

Associated Types

type Element (Maybe a) #

Methods

toList :: Maybe a -> [Element (Maybe a)] #

null :: Maybe a -> Bool #

foldr :: (Element (Maybe a) -> b -> b) -> b -> Maybe a -> b #

foldl :: (b -> Element (Maybe a) -> b) -> b -> Maybe a -> b #

foldl' :: (b -> Element (Maybe a) -> b) -> b -> Maybe a -> b #

length :: Maybe a -> Int #

elem :: Element (Maybe a) -> Maybe a -> Bool #

maximum :: Maybe a -> Element (Maybe a) #

minimum :: Maybe a -> Element (Maybe a) #

foldMap :: Monoid m => (Element (Maybe a) -> m) -> Maybe a -> m #

fold :: Maybe a -> Element (Maybe a) #

foldr' :: (Element (Maybe a) -> b -> b) -> b -> Maybe a -> b #

foldr1 :: (Element (Maybe a) -> Element (Maybe a) -> Element (Maybe a)) -> Maybe a -> Element (Maybe a) #

foldl1 :: (Element (Maybe a) -> Element (Maybe a) -> Element (Maybe a)) -> Maybe a -> Element (Maybe a) #

notElem :: Element (Maybe a) -> Maybe a -> Bool #

all :: (Element (Maybe a) -> Bool) -> Maybe a -> Bool #

any :: (Element (Maybe a) -> Bool) -> Maybe a -> Bool #

and :: Maybe a -> Bool #

or :: Maybe a -> Bool #

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

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

PMonoid (Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type Mempty :: a0 #

type Mappend arg0 arg1 :: a0 #

type Mconcat arg0 :: a0 #

SSemigroup a => SMonoid (Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Methods

sMempty :: Sing MemptySym0 #

sMappend :: forall (t1 :: Maybe a) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Apply (Apply MappendSym0 t1) t2) #

sMconcat :: forall (t :: [Maybe a]). Sing t -> Sing (Apply MconcatSym0 t) #

PShow (Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Show

Associated Types

type ShowsPrec arg0 arg1 arg2 :: Symbol #

type Show_ arg0 :: Symbol #

type ShowList arg0 arg1 :: Symbol #

SShow a => SShow (Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Show

Methods

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

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

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

PSemigroup (Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg0 <> arg1 :: a0 #

type Sconcat arg0 :: a0 #

SSemigroup a => SSemigroup (Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

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

sSconcat :: forall (t :: NonEmpty (Maybe a)). Sing t -> Sing (Apply SconcatSym0 t) #

POrd (Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

Associated Types

type Compare arg0 arg1 :: Ordering #

type arg0 < arg1 :: Bool #

type arg0 <= arg1 :: Bool #

type arg0 > arg1 :: Bool #

type arg0 >= arg1 :: Bool #

type Max arg0 arg1 :: a0 #

type Min arg0 arg1 :: a0 #

SOrd a => SOrd (Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

Methods

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

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

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

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

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

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

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

SEq a => SEq (Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Eq

Methods

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

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

PEq (Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Eq

Associated Types

type x == y :: Bool #

type x /= y :: Bool #

Pretty a => Pretty (Maybe a) 
Instance details

Defined in Text.PrettyPrint.Annotated.WL

Methods

pretty :: Maybe a -> Doc b #

prettyList :: [Maybe a] -> Doc b #

Pretty a => Pretty (Maybe a) 
Instance details

Defined in Text.PrettyPrint.Leijen.Text

Methods

pretty :: Maybe a -> Doc #

prettyList :: [Maybe a] -> Doc #

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

Defined in Lorentz.TypeAnns

Methods

getTypeAnn :: Notes (ToT (Maybe a)) Source #

Generic1 Maybe

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Maybe :: k -> Type #

Methods

from1 :: forall (a :: k). Maybe a -> Rep1 Maybe a #

to1 :: forall (a :: k). Rep1 Maybe a -> Maybe a #

IsoHKD Maybe (a :: Type) 
Instance details

Defined in Data.Vinyl.XRec

Associated Types

type HKD Maybe a #

Methods

unHKD :: HKD Maybe a -> Maybe a #

toHKD :: Maybe a -> HKD Maybe a #

SingI ('Nothing :: Maybe a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing 'Nothing

SDecide a => TestCoercion (SMaybe :: Maybe a -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Instances

Methods

testCoercion :: forall (a0 :: k) (b :: k). SMaybe a0 -> SMaybe b -> Maybe (Coercion a0 b) #

SDecide a => TestEquality (SMaybe :: Maybe a -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Instances

Methods

testEquality :: forall (a0 :: k) (b :: k). SMaybe a0 -> SMaybe b -> Maybe (a0 :~: b) #

(Eq a) :=> (Eq (Maybe a)) 
Instance details

Defined in Data.Constraint

Methods

ins :: Eq a :- Eq (Maybe a) #

(Ord a) :=> (Ord (Maybe a)) 
Instance details

Defined in Data.Constraint

Methods

ins :: Ord a :- Ord (Maybe a) #

(Read a) :=> (Read (Maybe a)) 
Instance details

Defined in Data.Constraint

Methods

ins :: Read a :- Read (Maybe a) #

(Show a) :=> (Show (Maybe a)) 
Instance details

Defined in Data.Constraint

Methods

ins :: Show a :- Show (Maybe a) #

(Semigroup a) :=> (Semigroup (Maybe a)) 
Instance details

Defined in Data.Constraint

Methods

ins :: Semigroup a :- Semigroup (Maybe a) #

(Monoid a) :=> (Monoid (Maybe a)) 
Instance details

Defined in Data.Constraint

Methods

ins :: Monoid a :- Monoid (Maybe a) #

Each (Maybe a) (Maybe b) a b 
Instance details

Defined in Lens.Micro.Internal

Methods

each :: Traversal (Maybe a) (Maybe b) a b #

CanCastTo a b => CanCastTo (Maybe a :: Type) (Maybe b :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (Maybe a) -> Proxy (Maybe b) -> () Source #

SingI a2 => SingI ('Just a2 :: Maybe a1)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing ('Just a2)

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 (CatMaybesSym0 :: TyFun [Maybe a6989586621679913394] [a6989586621679913394] -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

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

Defined in Data.Singletons.Prelude.Maybe

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

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (TFHelper_6989586621680024600Sym0 :: TyFun (Maybe a6989586621679962884) (Maybe a6989586621679962884 ~> Maybe a6989586621679962884) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

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

Defined in Data.Singletons.Prelude.Maybe

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

Defined in Data.Singletons.Prelude.Maybe

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

Defined in Data.Singletons.Prelude.Maybe

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

Defined in Data.Singletons.Prelude.Maybe

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings (Pure_6989586621680024315Sym0 :: TyFun a6989586621679962808 (Maybe a6989586621679962808) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

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

Defined in Data.Singletons.Prelude.Monad.Internal

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

Defined in Data.Singletons.Prelude.Maybe

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

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (JustSym0 :: TyFun a3530822107858468865 (Maybe a3530822107858468865) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Instances

SuppressUnusedWarnings (GetOptionSym0 :: TyFun (Option a6989586621679060063) (Maybe a6989586621679060063) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.List.Internal

SingI d => SingI (FindSym1 d :: TyFun [a] (Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (FindSym1 d) #

SingI d => SingI (FindIndexSym1 d :: TyFun [a] (Maybe Nat) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (FindIndexSym1 d) #

(SEq a, SingI d) => SingI (ElemIndexSym1 d :: TyFun [a] (Maybe Nat) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing (ElemIndexSym1 d) #

SingI d => SingI (FromMaybeSym1 d :: TyFun (Maybe a) a -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

Methods

sing :: Sing (FromMaybeSym1 d) #

SAlternative f => SingI (OptionalSym0 :: TyFun (f a) (f (Maybe a)) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Applicative

SingI (Maybe_Sym0 :: TyFun b ((a ~> b) ~> (Maybe a ~> b)) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

Methods

sing :: Sing Maybe_Sym0 #

SEq a => SingI (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

Methods

sing :: Sing LookupSym0 #

SingI (MapMaybeSym0 :: TyFun (a ~> Maybe b) ([a] ~> [b]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SingI (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.Foldable

Methods

sing :: Sing FindSym0 #

SuppressUnusedWarnings (StripPrefixSym1 a6989586621680440227 :: TyFun [a6989586621680438531] (Maybe [a6989586621680438531]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (FindSym1 a6989586621680320898 :: TyFun [a6989586621680316350] (Maybe a6989586621680316350) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (FindIndexSym1 a6989586621680320874 :: TyFun [a6989586621680316347] (Maybe Nat) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (ElemIndexSym1 a6989586621680320890 :: TyFun [a6989586621680316349] (Maybe Nat) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (ShowsPrec_6989586621680595735Sym1 a6989586621680595732 a3530822107858468865 :: TyFun (Maybe a3530822107858468865) (Symbol ~> Symbol) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings (TFHelper_6989586621680024600Sym1 a6989586621680024598 :: TyFun (Maybe a6989586621679962884) (Maybe a6989586621679962884) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (TFHelper_6989586621680024510Sym0 :: TyFun (Maybe a6989586621679962834) (Maybe b6989586621679962835 ~> Maybe b6989586621679962835) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (TFHelper_6989586621680024498Sym0 :: TyFun (Maybe a6989586621679962832) ((a6989586621679962832 ~> Maybe b6989586621679962833) ~> Maybe b6989586621679962833) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (TFHelper_6989586621680024355Sym0 :: TyFun (Maybe a6989586621679962814) (Maybe b6989586621679962815 ~> Maybe b6989586621679962815) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (FromMaybeSym1 a6989586621679913583 :: TyFun (Maybe a6989586621679913397) a6989586621679913397 -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (Compare_6989586621679803207Sym1 a6989586621679803205 :: TyFun (Maybe a3530822107858468865) Ordering -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Ord

SuppressUnusedWarnings (TFHelper_6989586621680024325Sym0 :: TyFun (Maybe (a6989586621679962809 ~> b6989586621679962810)) (Maybe a6989586621679962809 ~> Maybe b6989586621679962810) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (OptionalSym0 :: TyFun (f6989586621681393521 a6989586621681393522) (f6989586621681393521 (Maybe a6989586621681393522)) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Applicative

SuppressUnusedWarnings (TFHelper_6989586621680024177Sym0 :: TyFun a6989586621679962805 (Maybe b6989586621679962806 ~> Maybe a6989586621679962805) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (Maybe_Sym0 :: TyFun b6989586621679911960 ((a6989586621679911961 ~> b6989586621679911960) ~> (Maybe a6989586621679911961 ~> b6989586621679911960)) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

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

Defined in Data.Singletons.Prelude.List.Internal

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Fmap_6989586621680024164Sym0 :: TyFun (a6989586621679962803 ~> b6989586621679962804) (Maybe a6989586621679962803 ~> Maybe b6989586621679962804) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (MapMaybeSym0 :: TyFun (a6989586621679913392 ~> Maybe b6989586621679913393) ([a6989586621679913392] ~> [b6989586621679913393]) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

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

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (FindSym0 :: TyFun (a6989586621680742290 ~> Bool) (t6989586621680742289 a6989586621680742290 ~> Maybe a6989586621680742290) -> 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 (LookupSym1 a6989586621680320552 b6989586621680316329 :: TyFun [(a6989586621680316328, b6989586621680316329)] (Maybe b6989586621680316329) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

SuppressUnusedWarnings (TFHelper_6989586621680024510Sym1 a6989586621680024508 b6989586621679962835 :: TyFun (Maybe b6989586621679962835) (Maybe b6989586621679962835) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (TFHelper_6989586621680024355Sym1 a6989586621680024353 b6989586621679962815 :: TyFun (Maybe b6989586621679962815) (Maybe b6989586621679962815) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (TFHelper_6989586621680024325Sym1 a6989586621680024323 :: TyFun (Maybe a6989586621679962809) (Maybe b6989586621679962810) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (TFHelper_6989586621680024177Sym1 a6989586621680024175 b6989586621679962806 :: TyFun (Maybe b6989586621679962806) (Maybe a6989586621679962805) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (Fmap_6989586621680024164Sym1 a6989586621680024162 :: TyFun (Maybe a6989586621679962803) (Maybe b6989586621679962804) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (Let6989586621680734313NSym1 x6989586621680734311 :: TyFun k1 (Maybe k1) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680734286NSym1 x6989586621680734284 :: TyFun k1 (Maybe k1) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (FindSym1 a6989586621680742743 t6989586621680742289 :: TyFun (t6989586621680742289 a6989586621680742290) (Maybe a6989586621680742290) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Monoid

SuppressUnusedWarnings (Traverse_6989586621680995058Sym0 :: TyFun (a6989586621680988964 ~> f6989586621680988963 b6989586621680988965) (Maybe a6989586621680988964 ~> f6989586621680988963 (Maybe b6989586621680988965)) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Traversable

SuppressUnusedWarnings (TFHelper_6989586621680024498Sym1 a6989586621680024496 b6989586621679962833 :: TyFun (a6989586621679962832 ~> Maybe b6989586621679962833) (Maybe b6989586621679962833) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (LiftA2_6989586621680024339Sym0 :: TyFun (a6989586621679962811 ~> (b6989586621679962812 ~> c6989586621679962813)) (Maybe a6989586621679962811 ~> (Maybe b6989586621679962812 ~> Maybe c6989586621679962813)) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (Maybe_Sym1 a6989586621679911978 a6989586621679911961 :: TyFun (a6989586621679911961 ~> b6989586621679911960) (Maybe a6989586621679911961 ~> b6989586621679911960) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

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

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (Let6989586621680743224MfSym0 :: 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 (Let6989586621680743199MfSym0 :: TyFun (k2 ~> (k3 ~> k2)) (TyFun k (TyFun k2 (TyFun (Maybe k3) (Maybe k2) -> Type) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

(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 (Traverse_6989586621680995058Sym1 a6989586621680995056 :: TyFun (Maybe a6989586621680988964) (f6989586621680988963 (Maybe b6989586621680988965)) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Traversable

SuppressUnusedWarnings (LiftA2_6989586621680024339Sym1 a6989586621680024336 :: TyFun (Maybe a6989586621679962811) (Maybe b6989586621679962812 ~> Maybe c6989586621679962813) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (Maybe_Sym2 a6989586621679911979 a6989586621679911978 :: TyFun (Maybe a6989586621679911961) b6989586621679911960 -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

SuppressUnusedWarnings (Let6989586621680743224MfSym1 f6989586621680743222 :: TyFun k (TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680743199MfSym1 f6989586621680743197 :: TyFun k (TyFun k2 (TyFun (Maybe k3) (Maybe k2) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Lambda_6989586621680641007Sym1 a6989586621680641005 :: TyFun (k1 ~> Last a) (TyFun k1 (Maybe a) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

SuppressUnusedWarnings (Lambda_6989586621680640919Sym1 a6989586621680640917 :: TyFun (k1 ~> First a) (TyFun k1 (Maybe a) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

SuppressUnusedWarnings (LiftA2_6989586621680024339Sym2 a6989586621680024337 a6989586621680024336 :: TyFun (Maybe b6989586621679962812) (Maybe c6989586621679962813) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

SuppressUnusedWarnings (Let6989586621680743224MfSym2 xs6989586621680743223 f6989586621680743222 :: TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680743199MfSym2 xs6989586621680743198 f6989586621680743197 :: TyFun k2 (TyFun (Maybe k3) (Maybe k2) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Lambda_6989586621680641007Sym2 k6989586621680641006 a6989586621680641005 :: TyFun k1 (Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

SuppressUnusedWarnings (Lambda_6989586621680640919Sym2 k6989586621680640918 a6989586621680640917 :: TyFun k1 (Maybe a) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

SuppressUnusedWarnings (Let6989586621680743199MfSym3 a6989586621680743200 xs6989586621680743198 f6989586621680743197 :: TyFun (Maybe k3) (Maybe k2) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

SuppressUnusedWarnings (Let6989586621680743224MfSym3 a6989586621680743225 xs6989586621680743223 f6989586621680743222 :: TyFun k3 (Maybe k3) -> Type) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

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

Defined in Michelson.Typed.Haskell.Value

Associated Types

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

Methods

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

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

(HasTypeAnn (Maybe a), KnownSymbol name) => HasTypeAnn (NamedF Maybe a name) Source # 
Instance details

Defined in Lorentz.TypeAnns

Methods

getTypeAnn :: Notes (ToT (NamedF Maybe a name)) Source #

type Failure Maybe 
Instance details

Defined in Basement.Monad

type Failure Maybe = ()
type StM Maybe a 
Instance details

Defined in Control.Monad.Trans.Control

type StM Maybe a = a
type Empty 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Empty = Empty_6989586621680024596Sym0 :: Maybe a
type Mzero 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Mzero = Mzero_6989586621679963350Sym0 :: Maybe a0
type Product (arg0 :: Maybe a0) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Product (arg0 :: Maybe a0) = Apply (Product_6989586621680743347Sym0 :: TyFun (Maybe a0) a0 -> Type) arg0
type Sum (arg0 :: Maybe a0) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Sum (arg0 :: Maybe a0) = Apply (Sum_6989586621680743334Sym0 :: TyFun (Maybe a0) a0 -> Type) arg0
type Minimum (arg0 :: Maybe a0) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Minimum (arg0 :: Maybe a0) = Apply (Minimum_6989586621680743321Sym0 :: TyFun (Maybe a0) a0 -> Type) arg0
type Maximum (arg0 :: Maybe a0) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Maximum (arg0 :: Maybe a0) = Apply (Maximum_6989586621680743308Sym0 :: TyFun (Maybe a0) a0 -> Type) arg0
type Length (arg0 :: Maybe a0) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Length (arg0 :: Maybe a0) = Apply (Length_6989586621680743270Sym0 :: TyFun (Maybe a0) Nat -> Type) arg0
type Null (arg0 :: Maybe a0) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Null (arg0 :: Maybe a0) = Apply (Null_6989586621680743249Sym0 :: TyFun (Maybe a0) Bool -> Type) arg0
type ToList (arg0 :: Maybe a0) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type ToList (arg0 :: Maybe a0) = Apply (ToList_6989586621680743240Sym0 :: TyFun (Maybe a0) [a0] -> Type) arg0
type Fold (arg0 :: Maybe m0) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Fold (arg0 :: Maybe m0) = Apply (Fold_6989586621680743057Sym0 :: TyFun (Maybe m0) m0 -> Type) arg0
type Fail a2 
Instance details

Defined in Data.Singletons.Prelude.Monad.Fail

type Fail a2 = Apply (Fail_6989586621680104793Sym0 :: TyFun [Char] (Maybe a1) -> Type) a2
type Pure (a :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Pure (a :: k1) = Apply (Pure_6989586621680024315Sym0 :: TyFun k1 (Maybe k1) -> Type) a
type Return (arg0 :: a0) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Return (arg0 :: a0) = Apply (Return_6989586621679963334Sym0 :: TyFun a0 (Maybe a0) -> Type) arg0
type Sequence (arg0 :: Maybe (m0 a0)) 
Instance details

Defined in Data.Singletons.Prelude.Traversable

type Sequence (arg0 :: Maybe (m0 a0)) = Apply (Sequence_6989586621680989026Sym0 :: TyFun (Maybe (m0 a0)) (m0 (Maybe a0)) -> Type) arg0
type SequenceA (arg0 :: Maybe (f0 a0)) 
Instance details

Defined in Data.Singletons.Prelude.Traversable

type SequenceA (arg0 :: Maybe (f0 a0)) = Apply (SequenceA_6989586621680989001Sym0 :: TyFun (Maybe (f0 a0)) (f0 (Maybe a0)) -> Type) arg0
type Elem (arg1 :: a0) (arg2 :: Maybe a0) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Elem (arg1 :: a0) (arg2 :: Maybe a0) = Apply (Apply (Elem_6989586621680743293Sym0 :: TyFun a0 (Maybe a0 ~> Bool) -> Type) arg1) arg2
type Foldl1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Maybe a0) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Maybe a0) = Apply (Apply (Foldl1_6989586621680743216Sym0 :: TyFun (a0 ~> (a0 ~> a0)) (Maybe a0 ~> a0) -> Type) arg1) arg2
type Foldr1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Maybe a0) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldr1 (arg1 :: a0 ~> (a0 ~> a0)) (arg2 :: Maybe a0) = Apply (Apply (Foldr1_6989586621680743191Sym0 :: TyFun (a0 ~> (a0 ~> a0)) (Maybe a0 ~> a0) -> Type) arg1) arg2
type (a1 :: Maybe a6989586621679962884) <|> (a2 :: Maybe a6989586621679962884) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type (a1 :: Maybe a6989586621679962884) <|> (a2 :: Maybe a6989586621679962884) = Apply (Apply (TFHelper_6989586621680024600Sym0 :: TyFun (Maybe a6989586621679962884) (Maybe a6989586621679962884 ~> Maybe a6989586621679962884) -> Type) a1) a2
type Mplus (arg1 :: Maybe a0) (arg2 :: Maybe a0) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Mplus (arg1 :: Maybe a0) (arg2 :: Maybe a0) = Apply (Apply (Mplus_6989586621679963354Sym0 :: TyFun (Maybe a0) (Maybe a0 ~> Maybe a0) -> Type) arg1) arg2
type FoldMap (a1 :: a6989586621680742384 ~> k2) (a2 :: Maybe a6989586621680742384) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type FoldMap (a1 :: a6989586621680742384 ~> k2) (a2 :: Maybe a6989586621680742384) = Apply (Apply (FoldMap_6989586621680743361Sym0 :: TyFun (a6989586621680742384 ~> k2) (Maybe a6989586621680742384 ~> k2) -> Type) a1) a2
type (a1 :: k1) <$ (a2 :: Maybe b6989586621679962806) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type (a1 :: k1) <$ (a2 :: Maybe b6989586621679962806) = Apply (Apply (TFHelper_6989586621680024177Sym0 :: TyFun k1 (Maybe b6989586621679962806 ~> Maybe k1) -> Type) a1) a2
type Fmap (a1 :: a6989586621679962803 ~> b6989586621679962804) (a2 :: Maybe a6989586621679962803) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Fmap (a1 :: a6989586621679962803 ~> b6989586621679962804) (a2 :: Maybe a6989586621679962803) = Apply (Apply (Fmap_6989586621680024164Sym0 :: TyFun (a6989586621679962803 ~> b6989586621679962804) (Maybe a6989586621679962803 ~> Maybe b6989586621679962804) -> Type) a1) a2
type (arg1 :: Maybe a0) <* (arg2 :: Maybe b0) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type (arg1 :: Maybe a0) <* (arg2 :: Maybe b0) = Apply (Apply (TFHelper_6989586621679963287Sym0 :: TyFun (Maybe a0) (Maybe b0 ~> Maybe a0) -> Type) arg1) arg2
type (a1 :: Maybe a6989586621679962814) *> (a2 :: Maybe b6989586621679962815) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type (a1 :: Maybe a6989586621679962814) *> (a2 :: Maybe b6989586621679962815) = Apply (Apply (TFHelper_6989586621680024355Sym0 :: TyFun (Maybe a6989586621679962814) (Maybe b6989586621679962815 ~> Maybe b6989586621679962815) -> Type) a1) a2
type (a1 :: Maybe (a6989586621679962809 ~> b6989586621679962810)) <*> (a2 :: Maybe a6989586621679962809) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type (a1 :: Maybe (a6989586621679962809 ~> b6989586621679962810)) <*> (a2 :: Maybe a6989586621679962809) = Apply (Apply (TFHelper_6989586621680024325Sym0 :: TyFun (Maybe (a6989586621679962809 ~> b6989586621679962810)) (Maybe a6989586621679962809 ~> Maybe b6989586621679962810) -> Type) a1) a2
type (a1 :: Maybe a6989586621679962834) >> (a2 :: Maybe b6989586621679962835) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type (a1 :: Maybe a6989586621679962834) >> (a2 :: Maybe b6989586621679962835) = Apply (Apply (TFHelper_6989586621680024510Sym0 :: TyFun (Maybe a6989586621679962834) (Maybe b6989586621679962835 ~> Maybe b6989586621679962835) -> Type) a1) a2
type (a1 :: Maybe a6989586621679962832) >>= (a2 :: a6989586621679962832 ~> Maybe b6989586621679962833) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type (a1 :: Maybe a6989586621679962832) >>= (a2 :: a6989586621679962832 ~> Maybe b6989586621679962833) = Apply (Apply (TFHelper_6989586621680024498Sym0 :: TyFun (Maybe a6989586621679962832) ((a6989586621679962832 ~> Maybe b6989586621679962833) ~> Maybe b6989586621679962833) -> Type) a1) a2
type MapM (arg1 :: a0 ~> m0 b0) (arg2 :: Maybe a0) 
Instance details

Defined in Data.Singletons.Prelude.Traversable

type MapM (arg1 :: a0 ~> m0 b0) (arg2 :: Maybe a0) = Apply (Apply (MapM_6989586621680989011Sym0 :: TyFun (a0 ~> m0 b0) (Maybe a0 ~> m0 (Maybe b0)) -> Type) arg1) arg2
type Traverse (a1 :: a6989586621680988964 ~> f6989586621680988963 b6989586621680988965) (a2 :: Maybe a6989586621680988964) 
Instance details

Defined in Data.Singletons.Prelude.Traversable

type Traverse (a1 :: a6989586621680988964 ~> f6989586621680988963 b6989586621680988965) (a2 :: Maybe a6989586621680988964) = Apply (Apply (Traverse_6989586621680995058Sym0 :: TyFun (a6989586621680988964 ~> f6989586621680988963 b6989586621680988965) (Maybe a6989586621680988964 ~> f6989586621680988963 (Maybe b6989586621680988965)) -> Type) a1) a2
type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Maybe a0) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl' (arg1 :: b0 ~> (a0 ~> b0)) (arg2 :: b0) (arg3 :: Maybe a0) = Apply (Apply (Apply (Foldl'_6989586621680743162Sym0 :: TyFun (b0 ~> (a0 ~> b0)) (b0 ~> (Maybe a0 ~> b0)) -> Type) arg1) arg2) arg3
type Foldl (a1 :: k2 ~> (a6989586621680742390 ~> k2)) (a2 :: k2) (a3 :: Maybe a6989586621680742390) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldl (a1 :: k2 ~> (a6989586621680742390 ~> k2)) (a2 :: k2) (a3 :: Maybe a6989586621680742390) = Apply (Apply (Apply (Foldl_6989586621680743396Sym0 :: TyFun (k2 ~> (a6989586621680742390 ~> k2)) (k2 ~> (Maybe a6989586621680742390 ~> k2)) -> Type) a1) a2) a3
type Foldr' (arg1 :: a0 ~> (b0 ~> b0)) (arg2 :: b0) (arg3 :: Maybe a0) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldr' (arg1 :: a0 ~> (b0 ~> b0)) (arg2 :: b0) (arg3 :: Maybe a0) = Apply (Apply (Apply (Foldr'_6989586621680743107Sym0 :: TyFun (a0 ~> (b0 ~> b0)) (b0 ~> (Maybe a0 ~> b0)) -> Type) arg1) arg2) arg3
type Foldr (a1 :: a6989586621680742385 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Maybe a6989586621680742385) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Foldr (a1 :: a6989586621680742385 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Maybe a6989586621680742385) = Apply (Apply (Apply (Foldr_6989586621680743378Sym0 :: TyFun (a6989586621680742385 ~> (k2 ~> k2)) (k2 ~> (Maybe a6989586621680742385 ~> k2)) -> Type) a1) a2) a3
type LiftA2 (a1 :: a6989586621679962811 ~> (b6989586621679962812 ~> c6989586621679962813)) (a2 :: Maybe a6989586621679962811) (a3 :: Maybe b6989586621679962812) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type LiftA2 (a1 :: a6989586621679962811 ~> (b6989586621679962812 ~> c6989586621679962813)) (a2 :: Maybe a6989586621679962811) (a3 :: Maybe b6989586621679962812) = Apply (Apply (Apply (LiftA2_6989586621680024339Sym0 :: TyFun (a6989586621679962811 ~> (b6989586621679962812 ~> c6989586621679962813)) (Maybe a6989586621679962811 ~> (Maybe b6989586621679962812 ~> Maybe c6989586621679962813)) -> Type) a1) a2) a3
type Apply (Pure_6989586621680024315Sym0 :: TyFun a (Maybe a) -> Type) (a6989586621680024314 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (Pure_6989586621680024315Sym0 :: TyFun a (Maybe a) -> Type) (a6989586621680024314 :: a) = Pure_6989586621680024315 a6989586621680024314
type Apply (Let6989586621680024608LSym0 :: TyFun k1 (Maybe k1) -> Type) (wild_69895866216800235866989586621680024607 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (Let6989586621680024608LSym0 :: TyFun k1 (Maybe k1) -> Type) (wild_69895866216800235866989586621680024607 :: k1) = Let6989586621680024608L wild_69895866216800235866989586621680024607
type Apply (JustSym0 :: TyFun a (Maybe a) -> Type) (t6989586621679707039 :: a) 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Apply (JustSym0 :: TyFun a (Maybe a) -> Type) (t6989586621679707039 :: a) = 'Just t6989586621679707039
type Apply (Let6989586621680734286NSym1 x6989586621680734284 :: TyFun k1 (Maybe k1) -> Type) (y6989586621680734285 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680734286NSym1 x6989586621680734284 :: TyFun k1 (Maybe k1) -> Type) (y6989586621680734285 :: k1) = Let6989586621680734286N x6989586621680734284 y6989586621680734285
type Apply (Let6989586621680734286MSym1 x6989586621680734284 :: TyFun k (Maybe k1) -> Type) (y6989586621680734285 :: k) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680734286MSym1 x6989586621680734284 :: TyFun k (Maybe k1) -> Type) (y6989586621680734285 :: k) = Let6989586621680734286M x6989586621680734284 y6989586621680734285
type Apply (Let6989586621680734313NSym1 x6989586621680734311 :: TyFun k1 (Maybe k1) -> Type) (y6989586621680734312 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680734313NSym1 x6989586621680734311 :: TyFun k1 (Maybe k1) -> Type) (y6989586621680734312 :: k1) = Let6989586621680734313N x6989586621680734311 y6989586621680734312
type Apply (Let6989586621680734313MSym1 x6989586621680734311 :: TyFun k (Maybe k1) -> Type) (y6989586621680734312 :: k) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680734313MSym1 x6989586621680734311 :: TyFun k (Maybe k1) -> Type) (y6989586621680734312 :: k) = Let6989586621680734313M x6989586621680734311 y6989586621680734312
type Apply (Lambda_6989586621680640919Sym2 k6989586621680640918 a6989586621680640917 :: TyFun k1 (Maybe a) -> Type) (t6989586621680640930 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (Lambda_6989586621680640919Sym2 k6989586621680640918 a6989586621680640917 :: TyFun k1 (Maybe a) -> Type) (t6989586621680640930 :: k1) = Lambda_6989586621680640919 k6989586621680640918 a6989586621680640917 t6989586621680640930
type Apply (Lambda_6989586621680641007Sym2 k6989586621680641006 a6989586621680641005 :: TyFun k1 (Maybe a) -> Type) (t6989586621680641018 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (Lambda_6989586621680641007Sym2 k6989586621680641006 a6989586621680641005 :: TyFun k1 (Maybe a) -> Type) (t6989586621680641018 :: k1) = Lambda_6989586621680641007 k6989586621680641006 a6989586621680641005 t6989586621680641018
type Apply (Let6989586621680743224MfSym3 a6989586621680743225 xs6989586621680743223 f6989586621680743222 :: TyFun k3 (Maybe k3) -> Type) (a6989586621680743226 :: k3) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680743224MfSym3 a6989586621680743225 xs6989586621680743223 f6989586621680743222 :: TyFun k3 (Maybe k3) -> Type) (a6989586621680743226 :: k3) = Let6989586621680743224Mf a6989586621680743225 xs6989586621680743223 f6989586621680743222 a6989586621680743226
type Apply (ShowsPrec_6989586621680595735Sym0 :: TyFun Nat (Maybe a3530822107858468865 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680595732 :: Nat) 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowsPrec_6989586621680595735Sym0 :: TyFun Nat (Maybe a3530822107858468865 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680595732 :: Nat) = ShowsPrec_6989586621680595735Sym1 a6989586621680595732 a3530822107858468865 :: TyFun (Maybe a3530822107858468865) (Symbol ~> Symbol) -> Type
type Apply (FromMaybeSym0 :: TyFun a6989586621679913397 (Maybe a6989586621679913397 ~> a6989586621679913397) -> Type) (a6989586621679913583 :: a6989586621679913397) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (FromMaybeSym0 :: TyFun a6989586621679913397 (Maybe a6989586621679913397 ~> a6989586621679913397) -> Type) (a6989586621679913583 :: a6989586621679913397) = FromMaybeSym1 a6989586621679913583
type Apply (ElemIndexSym0 :: TyFun a6989586621680316349 ([a6989586621680316349] ~> Maybe Nat) -> Type) (a6989586621680320890 :: a6989586621680316349) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ElemIndexSym0 :: TyFun a6989586621680316349 ([a6989586621680316349] ~> Maybe Nat) -> Type) (a6989586621680320890 :: a6989586621680316349) = ElemIndexSym1 a6989586621680320890
type Apply (TFHelper_6989586621680024177Sym0 :: TyFun a6989586621679962805 (Maybe b6989586621679962806 ~> Maybe a6989586621679962805) -> Type) (a6989586621680024175 :: a6989586621679962805) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621680024177Sym0 :: TyFun a6989586621679962805 (Maybe b6989586621679962806 ~> Maybe a6989586621679962805) -> Type) (a6989586621680024175 :: a6989586621679962805) = TFHelper_6989586621680024177Sym1 a6989586621680024175 b6989586621679962806 :: TyFun (Maybe b6989586621679962806) (Maybe a6989586621679962805) -> Type
type Apply (Maybe_Sym0 :: TyFun b6989586621679911960 ((a6989586621679911961 ~> b6989586621679911960) ~> (Maybe a6989586621679911961 ~> b6989586621679911960)) -> Type) (a6989586621679911978 :: b6989586621679911960) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (Maybe_Sym0 :: TyFun b6989586621679911960 ((a6989586621679911961 ~> b6989586621679911960) ~> (Maybe a6989586621679911961 ~> b6989586621679911960)) -> Type) (a6989586621679911978 :: b6989586621679911960) = Maybe_Sym1 a6989586621679911978 a6989586621679911961 :: TyFun (a6989586621679911961 ~> b6989586621679911960) (Maybe a6989586621679911961 ~> b6989586621679911960) -> Type
type Apply (LookupSym0 :: TyFun a6989586621680316328 ([(a6989586621680316328, b6989586621680316329)] ~> Maybe b6989586621680316329) -> Type) (a6989586621680320552 :: a6989586621680316328) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (LookupSym0 :: TyFun a6989586621680316328 ([(a6989586621680316328, b6989586621680316329)] ~> Maybe b6989586621680316329) -> Type) (a6989586621680320552 :: a6989586621680316328) = LookupSym1 a6989586621680320552 b6989586621680316329 :: TyFun [(a6989586621680316328, b6989586621680316329)] (Maybe b6989586621680316329) -> Type
type Apply (Let6989586621680734286NSym0 :: TyFun k (TyFun k1 (Maybe k1) -> Type) -> Type) (x6989586621680734284 :: k) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680734286NSym0 :: TyFun k (TyFun k1 (Maybe k1) -> Type) -> Type) (x6989586621680734284 :: k) = Let6989586621680734286NSym1 x6989586621680734284 :: TyFun k1 (Maybe k1) -> Type
type Apply (Let6989586621680734286MSym0 :: TyFun k1 (TyFun k (Maybe k1) -> Type) -> Type) (x6989586621680734284 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680734286MSym0 :: TyFun k1 (TyFun k (Maybe k1) -> Type) -> Type) (x6989586621680734284 :: k1) = Let6989586621680734286MSym1 x6989586621680734284 :: TyFun k (Maybe k1) -> Type
type Apply (Let6989586621680734313NSym0 :: TyFun k (TyFun k1 (Maybe k1) -> Type) -> Type) (x6989586621680734311 :: k) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680734313NSym0 :: TyFun k (TyFun k1 (Maybe k1) -> Type) -> Type) (x6989586621680734311 :: k) = Let6989586621680734313NSym1 x6989586621680734311 :: TyFun k1 (Maybe k1) -> Type
type Apply (Let6989586621680734313MSym0 :: TyFun k1 (TyFun k (Maybe k1) -> Type) -> Type) (x6989586621680734311 :: k1) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680734313MSym0 :: TyFun k1 (TyFun k (Maybe k1) -> Type) -> Type) (x6989586621680734311 :: k1) = Let6989586621680734313MSym1 x6989586621680734311 :: TyFun k (Maybe k1) -> Type
type Apply (Lambda_6989586621680640919Sym0 :: TyFun k (TyFun (k1 ~> First a) (TyFun k1 (Maybe a) -> Type) -> Type) -> Type) (a6989586621680640917 :: k) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (Lambda_6989586621680640919Sym0 :: TyFun k (TyFun (k1 ~> First a) (TyFun k1 (Maybe a) -> Type) -> Type) -> Type) (a6989586621680640917 :: k) = Lambda_6989586621680640919Sym1 a6989586621680640917 :: TyFun (k1 ~> First a) (TyFun k1 (Maybe a) -> Type) -> Type
type Apply (Lambda_6989586621680641007Sym0 :: TyFun k (TyFun (k1 ~> Last a) (TyFun k1 (Maybe a) -> Type) -> Type) -> Type) (a6989586621680641005 :: k) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (Lambda_6989586621680641007Sym0 :: TyFun k (TyFun (k1 ~> Last a) (TyFun k1 (Maybe a) -> Type) -> Type) -> Type) (a6989586621680641005 :: k) = Lambda_6989586621680641007Sym1 a6989586621680641005 :: TyFun (k1 ~> Last a) (TyFun k1 (Maybe a) -> Type) -> Type
type Apply (Let6989586621680743199MfSym1 f6989586621680743197 :: TyFun k (TyFun k2 (TyFun (Maybe k3) (Maybe k2) -> Type) -> Type) -> Type) (xs6989586621680743198 :: k) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680743199MfSym1 f6989586621680743197 :: TyFun k (TyFun k2 (TyFun (Maybe k3) (Maybe k2) -> Type) -> Type) -> Type) (xs6989586621680743198 :: k) = Let6989586621680743199MfSym2 f6989586621680743197 xs6989586621680743198
type Apply (Let6989586621680743224MfSym1 f6989586621680743222 :: TyFun k (TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) -> Type) (xs6989586621680743223 :: k) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680743224MfSym1 f6989586621680743222 :: TyFun k (TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) -> Type) (xs6989586621680743223 :: k) = Let6989586621680743224MfSym2 f6989586621680743222 xs6989586621680743223
type Apply (Let6989586621680743199MfSym2 xs6989586621680743198 f6989586621680743197 :: TyFun k2 (TyFun (Maybe k3) (Maybe k2) -> Type) -> Type) (a6989586621680743200 :: k2) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680743199MfSym2 xs6989586621680743198 f6989586621680743197 :: TyFun k2 (TyFun (Maybe k3) (Maybe k2) -> Type) -> Type) (a6989586621680743200 :: k2) = Let6989586621680743199MfSym3 xs6989586621680743198 f6989586621680743197 a6989586621680743200
type Rep (Maybe a) 
Instance details

Defined in GHC.Generics

type Rep (Maybe a) = D1 ('MetaData "Maybe" "GHC.Maybe" "base" 'False) (C1 ('MetaCons "Nothing" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Just" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))
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 Sing 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = SMaybe :: Maybe a -> Type
type TypeDocFieldDescriptions (Maybe a) 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type ToT (Maybe a) 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT (Maybe a) = 'TOption (ToT a)
type 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_6989586621680631384Sym0 :: Maybe a
type Demote (Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Demote (Maybe a) = Maybe (Demote a)
type Rep1 Maybe 
Instance details

Defined in GHC.Generics

type Rep1 Maybe = D1 ('MetaData "Maybe" "GHC.Maybe" "base" 'False) (C1 ('MetaCons "Nothing" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Just" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Mconcat (arg0 :: [Maybe a]) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Mconcat (arg0 :: [Maybe a]) = Apply (Mconcat_6989586621680631303Sym0 :: TyFun [Maybe a] (Maybe a) -> Type) arg0
type Show_ (arg0 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Show

type Show_ (arg0 :: Maybe a) = Apply (Show__6989586621680577846Sym0 :: TyFun (Maybe a) Symbol -> Type) arg0
type Sconcat (arg0 :: NonEmpty (Maybe a)) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sconcat (arg0 :: NonEmpty (Maybe a)) = Apply (Sconcat_6989586621680187691Sym0 :: TyFun (NonEmpty (Maybe a)) (Maybe a) -> Type) arg0
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_6989586621680631288Sym0 :: 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_6989586621680577854Sym0 :: 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_6989586621680187922Sym0 :: 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_6989586621679792614Sym0 :: 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_6989586621679792596Sym0 :: 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_6989586621679792578Sym0 :: 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_6989586621679792560Sym0 :: 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_6989586621679792542Sym0 :: 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_6989586621679792524Sym0 :: 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_6989586621679803207Sym0 :: 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_6989586621679776054 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_6989586621680595735Sym0 :: TyFun Nat (Maybe a1 ~> (Symbol ~> Symbol)) -> Type) a2) a3) a4
type Apply (FromJustSym0 :: TyFun (Maybe a) a -> Type) (a6989586621679913593 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (FromJustSym0 :: TyFun (Maybe a) a -> Type) (a6989586621679913593 :: Maybe a) = FromJust a6989586621679913593
type Apply (IsNothingSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679913596 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

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

Defined in Data.Singletons.Prelude.Maybe

type Apply (IsJustSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679913598 :: Maybe a) = IsJust a6989586621679913598
type Apply (FromMaybeSym1 a6989586621679913583 :: TyFun (Maybe a) a -> Type) (a6989586621679913584 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (FromMaybeSym1 a6989586621679913583 :: TyFun (Maybe a) a -> Type) (a6989586621679913584 :: Maybe a) = FromMaybe a6989586621679913583 a6989586621679913584
type Apply (Compare_6989586621679803207Sym1 a6989586621679803205 :: TyFun (Maybe a) Ordering -> Type) (a6989586621679803206 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Compare_6989586621679803207Sym1 a6989586621679803205 :: TyFun (Maybe a) Ordering -> Type) (a6989586621679803206 :: Maybe a) = Compare_6989586621679803207 a6989586621679803205 a6989586621679803206
type Apply (Maybe_Sym2 a6989586621679911979 a6989586621679911978 :: TyFun (Maybe a) b -> Type) (a6989586621679911980 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (Maybe_Sym2 a6989586621679911979 a6989586621679911978 :: TyFun (Maybe a) b -> Type) (a6989586621679911980 :: Maybe a) = Maybe_ a6989586621679911979 a6989586621679911978 a6989586621679911980
type Apply (CatMaybesSym0 :: TyFun [Maybe a] [a] -> Type) (a6989586621679913572 :: [Maybe a]) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (CatMaybesSym0 :: TyFun [Maybe a] [a] -> Type) (a6989586621679913572 :: [Maybe a]) = CatMaybes a6989586621679913572
type Apply (ListToMaybeSym0 :: TyFun [a] (Maybe a) -> Type) (a6989586621679913577 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (ListToMaybeSym0 :: TyFun [a] (Maybe a) -> Type) (a6989586621679913577 :: [a]) = ListToMaybe a6989586621679913577
type Apply (MaybeToListSym0 :: TyFun (Maybe a) [a] -> Type) (a6989586621679913580 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (MaybeToListSym0 :: TyFun (Maybe a) [a] -> Type) (a6989586621679913580 :: Maybe a) = MaybeToList a6989586621679913580
type Apply (MaxInternalSym0 :: TyFun (Maybe a) (MaxInternal a) -> Type) (t6989586621680733515 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MaxInternalSym0 :: TyFun (Maybe a) (MaxInternal a) -> Type) (t6989586621680733515 :: Maybe a) = 'MaxInternal t6989586621680733515
type Apply (MinInternalSym0 :: TyFun (Maybe a) (MinInternal a) -> Type) (t6989586621680733713 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (MinInternalSym0 :: TyFun (Maybe a) (MinInternal a) -> Type) (t6989586621680733713 :: Maybe a) = 'MinInternal t6989586621680733713
type Apply (OptionSym0 :: TyFun (Maybe a) (Option a) -> Type) (t6989586621680197015 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply (OptionSym0 :: TyFun (Maybe a) (Option a) -> Type) (t6989586621680197015 :: Maybe a) = 'Option t6989586621680197015
type Apply (FirstSym0 :: TyFun (Maybe a) (First a) -> Type) (t6989586621680634737 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (FirstSym0 :: TyFun (Maybe a) (First a) -> Type) (t6989586621680634737 :: Maybe a) = 'First t6989586621680634737
type Apply (LastSym0 :: TyFun (Maybe a) (Last a) -> Type) (t6989586621680634760 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (LastSym0 :: TyFun (Maybe a) (Last a) -> Type) (t6989586621680634760 :: Maybe a) = 'Last t6989586621680634760
type Apply (GetOptionSym0 :: TyFun (Option a) (Maybe a) -> Type) (a6989586621680197012 :: Option a) 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Monoid

type Apply (GetLastSym0 :: TyFun (Last a) (Maybe a) -> Type) (a6989586621680634757 :: Last a) = GetLast a6989586621680634757
type Apply (FindSym1 a6989586621680320898 :: TyFun [a] (Maybe a) -> Type) (a6989586621680320899 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FindSym1 a6989586621680320898 :: TyFun [a] (Maybe a) -> Type) (a6989586621680320899 :: [a]) = Find a6989586621680320898 a6989586621680320899
type Apply (FindIndexSym1 a6989586621680320874 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621680320875 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FindIndexSym1 a6989586621680320874 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621680320875 :: [a]) = FindIndex a6989586621680320874 a6989586621680320875
type Apply (ElemIndexSym1 a6989586621680320890 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621680320891 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (ElemIndexSym1 a6989586621680320890 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621680320891 :: [a]) = ElemIndex a6989586621680320890 a6989586621680320891
type Apply (StripPrefixSym1 a6989586621680440227 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621680440228 :: [a]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (StripPrefixSym1 a6989586621680440227 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621680440228 :: [a]) = StripPrefix a6989586621680440227 a6989586621680440228
type Apply (TFHelper_6989586621680024600Sym1 a6989586621680024598 :: TyFun (Maybe a) (Maybe a) -> Type) (a6989586621680024599 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621680024600Sym1 a6989586621680024598 :: TyFun (Maybe a) (Maybe a) -> Type) (a6989586621680024599 :: Maybe a) = TFHelper_6989586621680024600 a6989586621680024598 a6989586621680024599
type Apply (OptionalSym0 :: TyFun (f a) (f (Maybe a)) -> Type) (a6989586621681393559 :: f a) 
Instance details

Defined in Data.Singletons.Prelude.Applicative

type Apply (OptionalSym0 :: TyFun (f a) (f (Maybe a)) -> Type) (a6989586621681393559 :: f a) = Optional a6989586621681393559
type Apply (LookupSym1 a6989586621680320552 b :: TyFun [(a, b)] (Maybe b) -> Type) (a6989586621680320553 :: [(a, b)]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (LookupSym1 a6989586621680320552 b :: TyFun [(a, b)] (Maybe b) -> Type) (a6989586621680320553 :: [(a, b)]) = Lookup a6989586621680320552 a6989586621680320553
type Apply (Fmap_6989586621680024164Sym1 a6989586621680024162 :: TyFun (Maybe a) (Maybe b) -> Type) (a6989586621680024163 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (Fmap_6989586621680024164Sym1 a6989586621680024162 :: TyFun (Maybe a) (Maybe b) -> Type) (a6989586621680024163 :: Maybe a) = Fmap_6989586621680024164 a6989586621680024162 a6989586621680024163
type Apply (TFHelper_6989586621680024177Sym1 a6989586621680024175 b :: TyFun (Maybe b) (Maybe a) -> Type) (a6989586621680024176 :: Maybe b) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621680024177Sym1 a6989586621680024175 b :: TyFun (Maybe b) (Maybe a) -> Type) (a6989586621680024176 :: Maybe b) = TFHelper_6989586621680024177 a6989586621680024175 a6989586621680024176
type Apply (TFHelper_6989586621680024325Sym1 a6989586621680024323 :: TyFun (Maybe a) (Maybe b) -> Type) (a6989586621680024324 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621680024325Sym1 a6989586621680024323 :: TyFun (Maybe a) (Maybe b) -> Type) (a6989586621680024324 :: Maybe a) = TFHelper_6989586621680024325 a6989586621680024323 a6989586621680024324
type Apply (TFHelper_6989586621680024355Sym1 a6989586621680024353 b :: TyFun (Maybe b) (Maybe b) -> Type) (a6989586621680024354 :: Maybe b) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621680024355Sym1 a6989586621680024353 b :: TyFun (Maybe b) (Maybe b) -> Type) (a6989586621680024354 :: Maybe b) = TFHelper_6989586621680024355 a6989586621680024353 a6989586621680024354
type Apply (TFHelper_6989586621680024510Sym1 a6989586621680024508 b :: TyFun (Maybe b) (Maybe b) -> Type) (a6989586621680024509 :: Maybe b) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621680024510Sym1 a6989586621680024508 b :: TyFun (Maybe b) (Maybe b) -> Type) (a6989586621680024509 :: Maybe b) = TFHelper_6989586621680024510 a6989586621680024508 a6989586621680024509
type Apply (FindSym1 a6989586621680742743 t :: TyFun (t a) (Maybe a) -> Type) (a6989586621680742744 :: t a) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FindSym1 a6989586621680742743 t :: TyFun (t a) (Maybe a) -> Type) (a6989586621680742744 :: t a) = Find a6989586621680742743 a6989586621680742744
type Apply (Traverse_6989586621680995058Sym1 a6989586621680995056 :: TyFun (Maybe a) (f (Maybe b)) -> Type) (a6989586621680995057 :: Maybe a) 
Instance details

Defined in Data.Singletons.Prelude.Traversable

type Apply (Traverse_6989586621680995058Sym1 a6989586621680995056 :: TyFun (Maybe a) (f (Maybe b)) -> Type) (a6989586621680995057 :: Maybe a) = Traverse_6989586621680995058 a6989586621680995056 a6989586621680995057
type Apply (LiftA2_6989586621680024339Sym2 a6989586621680024337 a6989586621680024336 :: TyFun (Maybe b) (Maybe c) -> Type) (a6989586621680024338 :: Maybe b) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (LiftA2_6989586621680024339Sym2 a6989586621680024337 a6989586621680024336 :: TyFun (Maybe b) (Maybe c) -> Type) (a6989586621680024338 :: Maybe b) = LiftA2_6989586621680024339 a6989586621680024337 a6989586621680024336 a6989586621680024338
type Apply (Let6989586621680743199MfSym3 a6989586621680743200 xs6989586621680743198 f6989586621680743197 :: TyFun (Maybe k3) (Maybe k2) -> Type) (a6989586621680743201 :: Maybe k3) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680743199MfSym3 a6989586621680743200 xs6989586621680743198 f6989586621680743197 :: TyFun (Maybe k3) (Maybe k2) -> Type) (a6989586621680743201 :: Maybe k3) = Let6989586621680743199Mf a6989586621680743200 xs6989586621680743198 f6989586621680743197 a6989586621680743201
type Eval (Init (a2 ': (b ': as)) :: Maybe [a1] -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (Init (a2 ': (b ': as)) :: Maybe [a1] -> Type) = Eval ((Map (Cons a2) :: Maybe [a1] -> Maybe [a1] -> Type) =<< Init (b ': as))
type Eval (Init '[a2] :: Maybe [a1] -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (Init '[a2] :: Maybe [a1] -> Type) = 'Just ('[] :: [a1])
type Eval (Init ('[] :: [a]) :: Maybe [a] -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (Init ('[] :: [a]) :: Maybe [a] -> Type) = 'Nothing :: Maybe [a]
type Eval (Tail (_a ': as) :: Maybe [a] -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (Tail (_a ': as) :: Maybe [a] -> Type) = 'Just as
type Eval (Tail ('[] :: [a]) :: Maybe [a] -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (Tail ('[] :: [a]) :: Maybe [a] -> Type) = 'Nothing :: Maybe [a]
type Eval (Head (a2 ': _as) :: Maybe a1 -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (Head (a2 ': _as) :: Maybe a1 -> Type) = 'Just a2
type Eval (Head ('[] :: [a]) :: Maybe a -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (Head ('[] :: [a]) :: Maybe a -> Type) = 'Nothing :: Maybe a
type Eval (Last (a2 ': (b ': as)) :: Maybe a1 -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (Last (a2 ': (b ': as)) :: Maybe a1 -> Type) = Eval (Last (b ': as))
type Eval (Last '[a2] :: Maybe a1 -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (Last '[a2] :: Maybe a1 -> Type) = 'Just a2
type Eval (Last ('[] :: [a]) :: Maybe a -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (Last ('[] :: [a]) :: Maybe a -> Type) = 'Nothing :: Maybe a
type Apply (StripPrefixSym0 :: TyFun [a6989586621680438531] ([a6989586621680438531] ~> Maybe [a6989586621680438531]) -> Type) (a6989586621680440227 :: [a6989586621680438531]) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (StripPrefixSym0 :: TyFun [a6989586621680438531] ([a6989586621680438531] ~> Maybe [a6989586621680438531]) -> Type) (a6989586621680440227 :: [a6989586621680438531]) = StripPrefixSym1 a6989586621680440227
type Apply (TFHelper_6989586621680024600Sym0 :: TyFun (Maybe a6989586621679962884) (Maybe a6989586621679962884 ~> Maybe a6989586621679962884) -> Type) (a6989586621680024598 :: Maybe a6989586621679962884) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621680024600Sym0 :: TyFun (Maybe a6989586621679962884) (Maybe a6989586621679962884 ~> Maybe a6989586621679962884) -> Type) (a6989586621680024598 :: Maybe a6989586621679962884) = TFHelper_6989586621680024600Sym1 a6989586621680024598
type Apply (Compare_6989586621679803207Sym0 :: TyFun (Maybe a3530822107858468865) (Maybe a3530822107858468865 ~> Ordering) -> Type) (a6989586621679803205 :: Maybe a3530822107858468865) 
Instance details

Defined in Data.Singletons.Prelude.Ord

type Apply (Compare_6989586621679803207Sym0 :: TyFun (Maybe a3530822107858468865) (Maybe a3530822107858468865 ~> Ordering) -> Type) (a6989586621679803205 :: Maybe a3530822107858468865) = Compare_6989586621679803207Sym1 a6989586621679803205
type Apply (ShowsPrec_6989586621680595735Sym1 a6989586621680595732 a3530822107858468865 :: TyFun (Maybe a3530822107858468865) (Symbol ~> Symbol) -> Type) (a6989586621680595733 :: Maybe a3530822107858468865) 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowsPrec_6989586621680595735Sym1 a6989586621680595732 a3530822107858468865 :: TyFun (Maybe a3530822107858468865) (Symbol ~> Symbol) -> Type) (a6989586621680595733 :: Maybe a3530822107858468865) = ShowsPrec_6989586621680595735Sym2 a6989586621680595732 a6989586621680595733
type Apply (TFHelper_6989586621680024355Sym0 :: TyFun (Maybe a6989586621679962814) (Maybe b6989586621679962815 ~> Maybe b6989586621679962815) -> Type) (a6989586621680024353 :: Maybe a6989586621679962814) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621680024355Sym0 :: TyFun (Maybe a6989586621679962814) (Maybe b6989586621679962815 ~> Maybe b6989586621679962815) -> Type) (a6989586621680024353 :: Maybe a6989586621679962814) = TFHelper_6989586621680024355Sym1 a6989586621680024353 b6989586621679962815 :: TyFun (Maybe b6989586621679962815) (Maybe b6989586621679962815) -> Type
type Apply (TFHelper_6989586621680024498Sym0 :: TyFun (Maybe a6989586621679962832) ((a6989586621679962832 ~> Maybe b6989586621679962833) ~> Maybe b6989586621679962833) -> Type) (a6989586621680024496 :: Maybe a6989586621679962832) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621680024498Sym0 :: TyFun (Maybe a6989586621679962832) ((a6989586621679962832 ~> Maybe b6989586621679962833) ~> Maybe b6989586621679962833) -> Type) (a6989586621680024496 :: Maybe a6989586621679962832) = TFHelper_6989586621680024498Sym1 a6989586621680024496 b6989586621679962833 :: TyFun (a6989586621679962832 ~> Maybe b6989586621679962833) (Maybe b6989586621679962833) -> Type
type Apply (TFHelper_6989586621680024510Sym0 :: TyFun (Maybe a6989586621679962834) (Maybe b6989586621679962835 ~> Maybe b6989586621679962835) -> Type) (a6989586621680024508 :: Maybe a6989586621679962834) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621680024510Sym0 :: TyFun (Maybe a6989586621679962834) (Maybe b6989586621679962835 ~> Maybe b6989586621679962835) -> Type) (a6989586621680024508 :: Maybe a6989586621679962834) = TFHelper_6989586621680024510Sym1 a6989586621680024508 b6989586621679962835 :: TyFun (Maybe b6989586621679962835) (Maybe b6989586621679962835) -> Type
type Apply (TFHelper_6989586621680024325Sym0 :: TyFun (Maybe (a6989586621679962809 ~> b6989586621679962810)) (Maybe a6989586621679962809 ~> Maybe b6989586621679962810) -> Type) (a6989586621680024323 :: Maybe (a6989586621679962809 ~> b6989586621679962810)) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621680024325Sym0 :: TyFun (Maybe (a6989586621679962809 ~> b6989586621679962810)) (Maybe a6989586621679962809 ~> Maybe b6989586621679962810) -> Type) (a6989586621680024323 :: Maybe (a6989586621679962809 ~> b6989586621679962810)) = TFHelper_6989586621680024325Sym1 a6989586621680024323
type Apply (LiftA2_6989586621680024339Sym1 a6989586621680024336 :: TyFun (Maybe a6989586621679962811) (Maybe b6989586621679962812 ~> Maybe c6989586621679962813) -> Type) (a6989586621680024337 :: Maybe a6989586621679962811) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (LiftA2_6989586621680024339Sym1 a6989586621680024336 :: TyFun (Maybe a6989586621679962811) (Maybe b6989586621679962812 ~> Maybe c6989586621679962813) -> Type) (a6989586621680024337 :: Maybe a6989586621679962811) = LiftA2_6989586621680024339Sym2 a6989586621680024336 a6989586621680024337
type Apply (Let6989586621680743224MfSym2 xs6989586621680743223 f6989586621680743222 :: TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) (a6989586621680743225 :: Maybe k2) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680743224MfSym2 xs6989586621680743223 f6989586621680743222 :: TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) (a6989586621680743225 :: Maybe k2) = Let6989586621680743224MfSym3 xs6989586621680743223 f6989586621680743222 a6989586621680743225
type Eval (FindIndex p (a2 ': as) :: Maybe Nat -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (FindIndex p (a2 ': as) :: Maybe Nat -> Type) = Eval (If (Eval (p a2)) (Pure ('Just 0)) ((Map ((+) 1) :: Maybe Nat -> Maybe Nat -> Type) =<< FindIndex p as))
type Eval (FindIndex _p ('[] :: [a]) :: Maybe Nat -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (FindIndex _p ('[] :: [a]) :: Maybe Nat -> Type) = 'Nothing :: Maybe Nat
type Eval (NumIter a s :: Maybe (k, Nat) -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (NumIter a s :: Maybe (k, Nat) -> Type) = If (Eval (s > 0)) ('Just '(a, s - 1)) ('Nothing :: Maybe (k, Nat))
type Eval (Find p (a2 ': as) :: Maybe a1 -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (Find p (a2 ': as) :: Maybe a1 -> Type) = Eval (If (Eval (p a2)) (Pure ('Just a2)) (Find p as))
type Eval (Find _p ('[] :: [a]) :: Maybe a -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (Find _p ('[] :: [a]) :: Maybe a -> Type) = 'Nothing :: Maybe a
type Eval (Lookup a as :: Maybe b -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (Lookup a as :: Maybe b -> Type) = Eval (Map (Snd :: (k, b) -> b -> Type) (Eval (Find ((TyEq a :: k -> Bool -> Type) <=< (Fst :: (k, b) -> k -> Type)) as)))
type Eval (Map f ('Just a3) :: Maybe a2 -> Type) 
Instance details

Defined in Fcf.Classes

type Eval (Map f ('Just a3) :: Maybe a2 -> Type) = 'Just (Eval (f a3))
type Eval (Map f ('Nothing :: Maybe a) :: Maybe b -> Type) 
Instance details

Defined in Fcf.Classes

type Eval (Map f ('Nothing :: Maybe a) :: Maybe b -> Type) = 'Nothing :: Maybe b
type Eval ('Just x <|> _1 :: Maybe a -> Type) 
Instance details

Defined in Util.Fcf

type Eval ('Just x <|> _1 :: Maybe a -> Type) = 'Just x
type Eval (('Nothing :: Maybe a) <|> m :: Maybe a -> Type) 
Instance details

Defined in Util.Fcf

type Eval (('Nothing :: Maybe a) <|> m :: Maybe a -> Type) = m
type Apply (TFHelper_6989586621680024498Sym1 a6989586621680024496 b :: TyFun (a ~> Maybe b) (Maybe b) -> Type) (a6989586621680024497 :: a ~> Maybe b) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (TFHelper_6989586621680024498Sym1 a6989586621680024496 b :: TyFun (a ~> Maybe b) (Maybe b) -> Type) (a6989586621680024497 :: a ~> Maybe b) = TFHelper_6989586621680024498 a6989586621680024496 a6989586621680024497
type Apply (FindSym0 :: TyFun (a6989586621680316350 ~> Bool) ([a6989586621680316350] ~> Maybe a6989586621680316350) -> Type) (a6989586621680320898 :: a6989586621680316350 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FindSym0 :: TyFun (a6989586621680316350 ~> Bool) ([a6989586621680316350] ~> Maybe a6989586621680316350) -> Type) (a6989586621680320898 :: a6989586621680316350 ~> Bool) = FindSym1 a6989586621680320898
type Apply (FindIndexSym0 :: TyFun (a6989586621680316347 ~> Bool) ([a6989586621680316347] ~> Maybe Nat) -> Type) (a6989586621680320874 :: a6989586621680316347 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (FindIndexSym0 :: TyFun (a6989586621680316347 ~> Bool) ([a6989586621680316347] ~> Maybe Nat) -> Type) (a6989586621680320874 :: a6989586621680316347 ~> Bool) = FindIndexSym1 a6989586621680320874
type Apply (Fmap_6989586621680024164Sym0 :: TyFun (a6989586621679962803 ~> b6989586621679962804) (Maybe a6989586621679962803 ~> Maybe b6989586621679962804) -> Type) (a6989586621680024162 :: a6989586621679962803 ~> b6989586621679962804) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (Fmap_6989586621680024164Sym0 :: TyFun (a6989586621679962803 ~> b6989586621679962804) (Maybe a6989586621679962803 ~> Maybe b6989586621679962804) -> Type) (a6989586621680024162 :: a6989586621679962803 ~> b6989586621679962804) = Fmap_6989586621680024164Sym1 a6989586621680024162
type Apply (MapMaybeSym0 :: TyFun (a6989586621679913392 ~> Maybe b6989586621679913393) ([a6989586621679913392] ~> [b6989586621679913393]) -> Type) (a6989586621679913553 :: a6989586621679913392 ~> Maybe b6989586621679913393) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (MapMaybeSym0 :: TyFun (a6989586621679913392 ~> Maybe b6989586621679913393) ([a6989586621679913392] ~> [b6989586621679913393]) -> Type) (a6989586621679913553 :: a6989586621679913392 ~> Maybe b6989586621679913393) = MapMaybeSym1 a6989586621679913553
type Apply (UnfoldrSym0 :: TyFun (b6989586621680316406 ~> Maybe (a6989586621680316407, b6989586621680316406)) (b6989586621680316406 ~> [a6989586621680316407]) -> Type) (a6989586621680321318 :: b6989586621680316406 ~> Maybe (a6989586621680316407, b6989586621680316406)) 
Instance details

Defined in Data.Singletons.Prelude.List.Internal

type Apply (UnfoldrSym0 :: TyFun (b6989586621680316406 ~> Maybe (a6989586621680316407, b6989586621680316406)) (b6989586621680316406 ~> [a6989586621680316407]) -> Type) (a6989586621680321318 :: b6989586621680316406 ~> Maybe (a6989586621680316407, b6989586621680316406)) = UnfoldrSym1 a6989586621680321318
type Apply (FindSym0 :: TyFun (a6989586621680742290 ~> Bool) (t6989586621680742289 a6989586621680742290 ~> Maybe a6989586621680742290) -> Type) (a6989586621680742743 :: a6989586621680742290 ~> Bool) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (FindSym0 :: TyFun (a6989586621680742290 ~> Bool) (t6989586621680742289 a6989586621680742290 ~> Maybe a6989586621680742290) -> Type) (a6989586621680742743 :: a6989586621680742290 ~> Bool) = FindSym1 a6989586621680742743 t6989586621680742289 :: TyFun (t6989586621680742289 a6989586621680742290) (Maybe a6989586621680742290) -> Type
type Apply (Traverse_6989586621680995058Sym0 :: TyFun (a6989586621680988964 ~> f6989586621680988963 b6989586621680988965) (Maybe a6989586621680988964 ~> f6989586621680988963 (Maybe b6989586621680988965)) -> Type) (a6989586621680995056 :: a6989586621680988964 ~> f6989586621680988963 b6989586621680988965) 
Instance details

Defined in Data.Singletons.Prelude.Traversable

type Apply (Traverse_6989586621680995058Sym0 :: TyFun (a6989586621680988964 ~> f6989586621680988963 b6989586621680988965) (Maybe a6989586621680988964 ~> f6989586621680988963 (Maybe b6989586621680988965)) -> Type) (a6989586621680995056 :: a6989586621680988964 ~> f6989586621680988963 b6989586621680988965) = Traverse_6989586621680995058Sym1 a6989586621680995056
type Apply (LiftA2_6989586621680024339Sym0 :: TyFun (a6989586621679962811 ~> (b6989586621679962812 ~> c6989586621679962813)) (Maybe a6989586621679962811 ~> (Maybe b6989586621679962812 ~> Maybe c6989586621679962813)) -> Type) (a6989586621680024336 :: a6989586621679962811 ~> (b6989586621679962812 ~> c6989586621679962813)) 
Instance details

Defined in Data.Singletons.Prelude.Monad.Internal

type Apply (LiftA2_6989586621680024339Sym0 :: TyFun (a6989586621679962811 ~> (b6989586621679962812 ~> c6989586621679962813)) (Maybe a6989586621679962811 ~> (Maybe b6989586621679962812 ~> Maybe c6989586621679962813)) -> Type) (a6989586621680024336 :: a6989586621679962811 ~> (b6989586621679962812 ~> c6989586621679962813)) = LiftA2_6989586621680024339Sym1 a6989586621680024336
type Apply (Maybe_Sym1 a6989586621679911978 a6989586621679911961 :: TyFun (a6989586621679911961 ~> b6989586621679911960) (Maybe a6989586621679911961 ~> b6989586621679911960) -> Type) (a6989586621679911979 :: a6989586621679911961 ~> b6989586621679911960) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (Maybe_Sym1 a6989586621679911978 a6989586621679911961 :: TyFun (a6989586621679911961 ~> b6989586621679911960) (Maybe a6989586621679911961 ~> b6989586621679911960) -> Type) (a6989586621679911979 :: a6989586621679911961 ~> b6989586621679911960) = Maybe_Sym2 a6989586621679911978 a6989586621679911979
type Apply (Let6989586621679913560RsSym0 :: TyFun (a6989586621679913392 ~> Maybe k1) (TyFun k (TyFun [a6989586621679913392] [k1] -> Type) -> Type) -> Type) (f6989586621679913557 :: a6989586621679913392 ~> Maybe k1) 
Instance details

Defined in Data.Singletons.Prelude.Maybe

type Apply (Let6989586621679913560RsSym0 :: TyFun (a6989586621679913392 ~> Maybe k1) (TyFun k (TyFun [a6989586621679913392] [k1] -> Type) -> Type) -> Type) (f6989586621679913557 :: a6989586621679913392 ~> Maybe k1) = Let6989586621679913560RsSym1 f6989586621679913557 :: TyFun k (TyFun [a6989586621679913392] [k1] -> Type) -> Type
type Apply (Let6989586621680743199MfSym0 :: TyFun (k2 ~> (k3 ~> k2)) (TyFun k (TyFun k2 (TyFun (Maybe k3) (Maybe k2) -> Type) -> Type) -> Type) -> Type) (f6989586621680743197 :: k2 ~> (k3 ~> k2)) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680743199MfSym0 :: TyFun (k2 ~> (k3 ~> k2)) (TyFun k (TyFun k2 (TyFun (Maybe k3) (Maybe k2) -> Type) -> Type) -> Type) -> Type) (f6989586621680743197 :: k2 ~> (k3 ~> k2)) = Let6989586621680743199MfSym1 f6989586621680743197 :: TyFun k (TyFun k2 (TyFun (Maybe k3) (Maybe k2) -> Type) -> Type) -> Type
type Apply (Let6989586621680743224MfSym0 :: TyFun (k2 ~> (k3 ~> k3)) (TyFun k (TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) -> Type) -> Type) (f6989586621680743222 :: k2 ~> (k3 ~> k3)) 
Instance details

Defined in Data.Singletons.Prelude.Foldable

type Apply (Let6989586621680743224MfSym0 :: TyFun (k2 ~> (k3 ~> k3)) (TyFun k (TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) -> Type) -> Type) (f6989586621680743222 :: k2 ~> (k3 ~> k3)) = Let6989586621680743224MfSym1 f6989586621680743222 :: TyFun k (TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621680640919Sym1 a6989586621680640917 :: TyFun (k1 ~> First a) (TyFun k1 (Maybe a) -> Type) -> Type) (k6989586621680640918 :: k1 ~> First a) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (Lambda_6989586621680640919Sym1 a6989586621680640917 :: TyFun (k1 ~> First a) (TyFun k1 (Maybe a) -> Type) -> Type) (k6989586621680640918 :: k1 ~> First a) = Lambda_6989586621680640919Sym2 a6989586621680640917 k6989586621680640918
type Apply (Lambda_6989586621680641007Sym1 a6989586621680641005 :: TyFun (k1 ~> Last a) (TyFun k1 (Maybe a) -> Type) -> Type) (k6989586621680641006 :: k1 ~> Last a) 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (Lambda_6989586621680641007Sym1 a6989586621680641005 :: TyFun (k1 ~> Last a) (TyFun k1 (Maybe a) -> Type) -> Type) (k6989586621680641006 :: k1 ~> Last a) = Lambda_6989586621680641007Sym2 a6989586621680641005 k6989586621680641006
type Unwrapped (NamedF Maybe a name) 
Instance details

Defined in Util.Named

type Unwrapped (NamedF Maybe a name) = Maybe a
type ToT (NamedF Maybe a name) 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT (NamedF Maybe a name) = ToT (Maybe a)

type List = [] Source #

data ContractRef arg #

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

Note that type argument always designates an argument of entrypoint. If a contract has explicit default entrypoint (and no root entrypoint), ContractRef referring to it can never have the entire parameter as its type argument.

Instances

Instances details
cp ~ cp' => FromContractRef cp (ContractRef cp') Source # 
Instance details

Defined in Lorentz.Address

cp ~ cp' => ToContractRef cp (ContractRef cp') Source # 
Instance details

Defined in Lorentz.Address

Eq (ContractRef arg) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Methods

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

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

Show (ContractRef arg) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Methods

showsPrec :: Int -> ContractRef arg -> ShowS #

show :: ContractRef arg -> String #

showList :: [ContractRef arg] -> ShowS #

WellTypedToT arg => Buildable (ContractRef arg) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Methods

build :: ContractRef arg -> Builder #

PolyTypeHasDocC '[cp] => TypeHasDoc (ContractRef cp) 
Instance details

Defined in Michelson.Typed.Haskell.Doc

WellTypedToT arg => IsoValue (ContractRef arg) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Associated Types

type ToT (ContractRef arg) :: T #

Methods

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

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

HasTypeAnn a => HasTypeAnn (ContractRef a) Source # 
Instance details

Defined in Lorentz.TypeAnns

ToAddress (ContractRef cp) Source # 
Instance details

Defined in Lorentz.Address

CanCastTo a1 a2 => CanCastTo (ContractRef a1 :: Type) (ContractRef a2 :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (ContractRef a1) -> Proxy (ContractRef a2) -> () Source #

type TypeDocFieldDescriptions (ContractRef cp) 
Instance details

Defined in Michelson.Typed.Haskell.Doc

type ToT (ContractRef arg) 
Instance details

Defined in Michelson.Typed.Haskell.Value

type ToT (ContractRef arg) = 'TContract (ToT arg)

newtype TAddress p Source #

Address which remembers the parameter type of the contract it refers to.

It differs from Michelson's contract type because it cannot contain entrypoint, and it always refers to entire contract parameter even if this contract has explicit default entrypoint.

Constructors

TAddress 

Fields

Instances

Instances details
(FailWhen cond msg, cond ~ (CanHaveEntryPoints cp && Not (ParameterEntryPointsDerivation cp == EpdNone)), msg ~ (((('Text "Cannot apply `ToContractRef` to `TAddress`" :$$: 'Text "Consider using call(Def)TAddress first`") :$$: 'Text "(or if you know your parameter type is primitive,") :$$: 'Text " make sure typechecker also knows about that)") :$$: (('Text "For parameter `" :<>: 'ShowType cp) :<>: 'Text "`")), cp ~ arg, NiceParameter arg, NiceParameterFull cp, GetDefaultEntryPointArg cp ~ cp) => ToContractRef arg (TAddress cp) Source # 
Instance details

Defined in Lorentz.Address

cp ~ cp' => ToTAddress cp (TAddress cp') Source # 
Instance details

Defined in Lorentz.Address

Methods

toTAddress :: TAddress cp' -> TAddress cp Source #

CanCastTo Address (TAddress p :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy Address -> Proxy (TAddress p) -> () Source #

CanCastTo (TAddress p :: Type) Address Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (TAddress p) -> Proxy Address -> () Source #

Generic (TAddress p) Source # 
Instance details

Defined in Lorentz.Address

Associated Types

type Rep (TAddress p) :: Type -> Type #

Methods

from :: TAddress p -> Rep (TAddress p) x #

to :: Rep (TAddress p) x -> TAddress p #

IsoValue (TAddress p) Source # 
Instance details

Defined in Lorentz.Address

Associated Types

type ToT (TAddress p) :: T #

Methods

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

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

HasTypeAnn (TAddress p) Source # 
Instance details

Defined in Lorentz.Address

ToAddress (TAddress cp) Source # 
Instance details

Defined in Lorentz.Address

type Rep (TAddress p) Source # 
Instance details

Defined in Lorentz.Address

type Rep (TAddress p) = D1 ('MetaData "TAddress" "Lorentz.Address" "lorentz-0.4.0-4bB2PLHB7038abCZLw1vnA" 'True) (C1 ('MetaCons "TAddress" 'PrefixI 'True) (S1 ('MetaSel ('Just "unTAddress") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Address)))
type ToT (TAddress p) Source # 
Instance details

Defined in Lorentz.Address

newtype FutureContract arg Source #

Address associated with value of contract arg type.

Places where ContractRef can appear are now severely limited, this type gives you type-safety of ContractRef but still can be used everywhere. This type is not a full-featured one rather a helper; in particular, once pushing it on stack, you cannot return it back to Haskell world.

Note that it refers to an entrypoint of the contract, not just the contract as a whole. In this sense this type differs from TAddress.

Unlike with ContractRef, having this type you still cannot be sure that the referred contract exists and need to perform a lookup before calling it.

Constructors

FutureContract 

Instances

Instances details
cp ~ cp' => FromContractRef cp (FutureContract cp') Source # 
Instance details

Defined in Lorentz.Address

(NiceParameter cp, cp ~ cp') => ToContractRef cp (FutureContract cp') Source # 
Instance details

Defined in Lorentz.Address

IsoValue (FutureContract arg) Source # 
Instance details

Defined in Lorentz.Address

Associated Types

type ToT (FutureContract arg) :: T #

HasTypeAnn (FutureContract a) Source # 
Instance details

Defined in Lorentz.Address

ToAddress (FutureContract cp) Source # 
Instance details

Defined in Lorentz.Address

CanCastTo (FutureContract p :: Type) EpAddress Source # 
Instance details

Defined in Lorentz.Coercions

type ToT (FutureContract arg) Source # 
Instance details

Defined in Lorentz.Address

data EpName #

Entrypoint name.

Empty if this entrypoint is default one. Cannot be equal to "default", the reference implementation forbids that. Also, set of allowed characters should be the same as in annotations.

Instances

Instances details
Eq EpName 
Instance details

Defined in Michelson.Untyped.EntryPoints

Methods

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

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

Ord EpName 
Instance details

Defined in Michelson.Untyped.EntryPoints

Show EpName 
Instance details

Defined in Michelson.Untyped.EntryPoints

Generic EpName 
Instance details

Defined in Michelson.Untyped.EntryPoints

Associated Types

type Rep EpName :: Type -> Type #

Methods

from :: EpName -> Rep EpName x #

to :: Rep EpName x -> EpName #

Arbitrary FieldAnn => Arbitrary EpName 
Instance details

Defined in Michelson.Untyped.EntryPoints

NFData EpName 
Instance details

Defined in Michelson.Untyped.EntryPoints

Methods

rnf :: EpName -> () #

ToJSON EpName 
Instance details

Defined in Michelson.Untyped.EntryPoints

FromJSON EpName 
Instance details

Defined in Michelson.Untyped.EntryPoints

Default EpName 
Instance details

Defined in Michelson.Untyped.EntryPoints

Methods

def :: EpName #

Buildable EpName 
Instance details

Defined in Michelson.Untyped.EntryPoints

Methods

build :: EpName -> Builder #

HasCLReader EpName 
Instance details

Defined in Michelson.Untyped.EntryPoints

type Rep EpName 
Instance details

Defined in Michelson.Untyped.EntryPoints

type Rep EpName = D1 ('MetaData "EpName" "Michelson.Untyped.EntryPoints" "morley-1.4.0-FPgS4VJ0cLmB07ubDf4i8P" 'True) (C1 ('MetaCons "EpNameUnsafe" 'PrefixI 'True) (S1 ('MetaSel ('Just "unEpName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

pattern DefEpName :: EpName #

type EntryPointCall param arg = EntryPointCallT (ToT param) (ToT arg) #

Constructors

toMutez :: Word32 -> Mutez #

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 #

QuasyQuoter for constructing Michelson strings.

Validity of result will be checked at compile time. Note:

  • slash must be escaped
  • newline character must appear as 'n'
  • use quotes as is
  • other special characters are not allowed.

timestampQuote :: QuasiQuoter #

Quote a value of type Timestamp in yyyy-mm-ddThh:mm:ss[.sss]Z format.

>>> formatTimestamp [timestampQuote| 2019-02-21T16:54:12.2344523Z |]
"2019-02-21T16:54:12Z"

Inspired by 'time-quote' library.

Conversions

coerceContractRef :: ToT a ~ ToT b => ContractRef a -> ContractRef b #

Replace type argument of ContractAddr with isomorphic one.

callingTAddress :: forall cp mname. NiceParameterFull cp => TAddress cp -> EntryPointRef mname -> ContractRef (GetEntryPointArgCustom cp mname) Source #

Turn TAddress to ContractRef in Haskell world.

This is an analogy of address to contract convertion in Michelson world, thus you have to supply an entrypoint (or call the default one explicitly).

callingDefTAddress :: forall cp. NiceParameterFull cp => TAddress cp -> ContractRef (GetDefaultEntryPointArg cp) Source #

Specification of callTAddress to call the default entrypoint.

class ToAddress a where Source #

Convert something to Address in Haskell world.

Use this when you want to access state of the contract and are not interested in calling it.

Methods

toAddress :: a -> Address Source #

Instances

Instances details
ToAddress EpAddress Source # 
Instance details

Defined in Lorentz.Address

ToAddress Address Source # 
Instance details

Defined in Lorentz.Address

ToAddress (ContractRef cp) Source # 
Instance details

Defined in Lorentz.Address

ToAddress (FutureContract cp) Source # 
Instance details

Defined in Lorentz.Address

ToAddress (TAddress cp) Source # 
Instance details

Defined in Lorentz.Address

class ToTAddress (cp :: Type) (a :: Type) where Source #

Convert something referring to a contract (not specific entrypoint) to TAddress in Haskell world.

Methods

toTAddress :: a -> TAddress cp Source #

Instances

Instances details
ToTAddress cp Address Source # 
Instance details

Defined in Lorentz.Address

cp ~ cp' => ToTAddress cp (TAddress cp') Source # 
Instance details

Defined in Lorentz.Address

Methods

toTAddress :: TAddress cp' -> TAddress cp Source #

class ToContractRef (cp :: Type) (contract :: Type) where Source #

Convert something to ContractRef in Haskell world.

Methods

toContractRef :: HasCallStack => contract -> ContractRef cp Source #

Instances

Instances details
(NiceParameter cp, cp ~ cp') => ToContractRef cp (FutureContract cp') Source # 
Instance details

Defined in Lorentz.Address

cp ~ cp' => ToContractRef cp (ContractRef cp') Source # 
Instance details

Defined in Lorentz.Address

(FailWhen cond msg, cond ~ (CanHaveEntryPoints cp && Not (ParameterEntryPointsDerivation cp == EpdNone)), msg ~ (((('Text "Cannot apply `ToContractRef` to `TAddress`" :$$: 'Text "Consider using call(Def)TAddress first`") :$$: 'Text "(or if you know your parameter type is primitive,") :$$: 'Text " make sure typechecker also knows about that)") :$$: (('Text "For parameter `" :<>: 'ShowType cp) :<>: 'Text "`")), cp ~ arg, NiceParameter arg, NiceParameterFull cp, GetDefaultEntryPointArg cp ~ cp) => ToContractRef arg (TAddress cp) Source # 
Instance details

Defined in Lorentz.Address

class FromContractRef (cp :: Type) (contract :: Type) where Source #

Convert something from ContractAddr in Haskell world.

Methods

fromContractRef :: ContractRef cp -> contract Source #

Instances

Instances details
FromContractRef cp Address Source # 
Instance details

Defined in Lorentz.Address

FromContractRef cp EpAddress Source # 
Instance details

Defined in Lorentz.Address

cp ~ cp' => FromContractRef cp (FutureContract cp') Source # 
Instance details

Defined in Lorentz.Address

cp ~ cp' => FromContractRef cp (ContractRef cp') Source # 
Instance details

Defined in Lorentz.Address

convertContractRef :: forall cp contract2 contract1. (ToContractRef cp contract1, FromContractRef cp contract2) => contract1 -> contract2 Source #

Misc

class Default a where #

A class for types with a default value.

Minimal complete definition

Nothing

Methods

def :: a #

The default value for this type.

Instances

Instances details
Default Double 
Instance details

Defined in Data.Default.Class

Methods

def :: Double #

Default Float 
Instance details

Defined in Data.Default.Class

Methods

def :: Float #

Default Int 
Instance details

Defined in Data.Default.Class

Methods

def :: Int #

Default Int8 
Instance details

Defined in Data.Default.Class

Methods

def :: Int8 #

Default Int16 
Instance details

Defined in Data.Default.Class

Methods

def :: Int16 #

Default Int32 
Instance details

Defined in Data.Default.Class

Methods

def :: Int32 #

Default Int64 
Instance details

Defined in Data.Default.Class

Methods

def :: Int64 #

Default Integer 
Instance details

Defined in Data.Default.Class

Methods

def :: Integer #

Default Ordering 
Instance details

Defined in Data.Default.Class

Methods

def :: Ordering #

Default Word 
Instance details

Defined in Data.Default.Class

Methods

def :: Word #

Default Word8 
Instance details

Defined in Data.Default.Class

Methods

def :: Word8 #

Default Word16 
Instance details

Defined in Data.Default.Class

Methods

def :: Word16 #

Default Word32 
Instance details

Defined in Data.Default.Class

Methods

def :: Word32 #

Default Word64 
Instance details

Defined in Data.Default.Class

Methods

def :: Word64 #

Default () 
Instance details

Defined in Data.Default.Class

Methods

def :: () #

Default All 
Instance details

Defined in Data.Default.Class

Methods

def :: All #

Default Any 
Instance details

Defined in Data.Default.Class

Methods

def :: Any #

Default CShort 
Instance details

Defined in Data.Default.Class

Methods

def :: CShort #

Default CUShort 
Instance details

Defined in Data.Default.Class

Methods

def :: CUShort #

Default CInt 
Instance details

Defined in Data.Default.Class

Methods

def :: CInt #

Default CUInt 
Instance details

Defined in Data.Default.Class

Methods

def :: CUInt #

Default CLong 
Instance details

Defined in Data.Default.Class

Methods

def :: CLong #

Default CULong 
Instance details

Defined in Data.Default.Class

Methods

def :: CULong #

Default CLLong 
Instance details

Defined in Data.Default.Class

Methods

def :: CLLong #

Default CULLong 
Instance details

Defined in Data.Default.Class

Methods

def :: CULLong #

Default CFloat 
Instance details

Defined in Data.Default.Class

Methods

def :: CFloat #

Default CDouble 
Instance details

Defined in Data.Default.Class

Methods

def :: CDouble #

Default CPtrdiff 
Instance details

Defined in Data.Default.Class

Methods

def :: CPtrdiff #

Default CSize 
Instance details

Defined in Data.Default.Class

Methods

def :: CSize #

Default CSigAtomic 
Instance details

Defined in Data.Default.Class

Methods

def :: CSigAtomic #

Default CClock 
Instance details

Defined in Data.Default.Class

Methods

def :: CClock #

Default CTime 
Instance details

Defined in Data.Default.Class

Methods

def :: CTime #

Default CUSeconds 
Instance details

Defined in Data.Default.Class

Methods

def :: CUSeconds #

Default CSUSeconds 
Instance details

Defined in Data.Default.Class

Methods

def :: CSUSeconds #

Default CIntPtr 
Instance details

Defined in Data.Default.Class

Methods

def :: CIntPtr #

Default CUIntPtr 
Instance details

Defined in Data.Default.Class

Methods

def :: CUIntPtr #

Default CIntMax 
Instance details

Defined in Data.Default.Class

Methods

def :: CIntMax #

Default CUIntMax 
Instance details

Defined in Data.Default.Class

Methods

def :: CUIntMax #

Default RiddersParam 
Instance details

Defined in Numeric.RootFinding

Methods

def :: RiddersParam #

Default NewtonParam 
Instance details

Defined in Numeric.RootFinding

Methods

def :: NewtonParam #

Default MorleyLogs 
Instance details

Defined in Michelson.Interpret

Methods

def :: MorleyLogs #

Default OptimizerConf 
Instance details

Defined in Michelson.Optimizer

Methods

def :: OptimizerConf #

Default EpName 
Instance details

Defined in Michelson.Untyped.EntryPoints

Methods

def :: EpName #

Default Pos 
Instance details

Defined in Michelson.ErrorPos

Methods

def :: Pos #

Default SrcPos 
Instance details

Defined in Michelson.ErrorPos

Methods

def :: SrcPos #

Default InstrCallStack 
Instance details

Defined in Michelson.ErrorPos

Methods

def :: InstrCallStack #

Default ContParam

We use s as default value which is same as R's default.

Instance details

Defined in Statistics.Quantile

Methods

def :: ContParam #

Default [a] 
Instance details

Defined in Data.Default.Class

Methods

def :: [a] #

Default (Maybe a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Maybe a #

Integral a => Default (Ratio a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Ratio a #

Default a => Default (IO a) 
Instance details

Defined in Data.Default.Class

Methods

def :: IO a #

(Default a, RealFloat a) => Default (Complex a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Complex a #

Default (First a) 
Instance details

Defined in Data.Default.Class

Methods

def :: First a #

Default (Last a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Last a #

Default a => Default (Dual a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Dual a #

Default (Endo a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Endo a #

Num a => Default (Sum a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Sum a #

Num a => Default (Product a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Product a #

Default (DfsSettings x) 
Instance details

Defined in Michelson.Typed.Util

Methods

def :: DfsSettings x #

Default (UStore a) Source # 
Instance details

Defined in Lorentz.UStore.Types

Methods

def :: UStore a #

Default (Store a) Source # 
Instance details

Defined in Lorentz.Store

Methods

def :: Store a #

Default r => Default (e -> r) 
Instance details

Defined in Data.Default.Class

Methods

def :: e -> r #

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

Defined in Data.Default.Class

Methods

def :: (a, b) #

Default (BigMap k v) 
Instance details

Defined in Michelson.Typed.Haskell.Value

Methods

def :: BigMap k v #

Default (Annotation tag) 
Instance details

Defined in Michelson.Untyped.Annotation

Methods

def :: Annotation tag #

Default (k |~> v) Source # 
Instance details

Defined in Lorentz.UStore.Types

Methods

def :: k |~> v #

Default other => Default (StorageSkeleton storeTemplate other) Source # 
Instance details

Defined in Lorentz.Store

Methods

def :: StorageSkeleton storeTemplate other #

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

Defined in Data.Default.Class

Methods

def :: (a, b, c) #

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

Defined in Data.Default.Class

Methods

def :: (a, b, c, d) #

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

Defined in Data.Default.Class

Methods

def :: (a, b, c, d, e) #

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

Defined in Data.Default.Class

Methods

def :: (a, b, c, d, e, f) #

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

Defined in Data.Default.Class

Methods

def :: (a, b, c, d, e, f, g) #

data Label (name :: Symbol) where #

Proxy for a label type that includes the KnownSymbol constraint

Constructors

Label :: forall (name :: Symbol). KnownSymbol name => Label name 

Instances

Instances details
(KnownSymbol name, s ~ name) => IsLabel s (Label name) 
Instance details

Defined in Util.Label

Methods

fromLabel :: Label name #

Eq (Label name) 
Instance details

Defined in Util.Label

Methods

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

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

Show (Label name) 
Instance details

Defined in Util.Label

Methods

showsPrec :: Int -> Label name -> ShowS #

show :: Label name -> String #

showList :: [Label name] -> ShowS #

Buildable (Label name) 
Instance details

Defined in Util.Label

Methods

build :: Label name -> Builder #