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

Lorentz.Value

Description

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

Synopsis

Documentation

type Value = Value' Instr #

class WellTypedToT a => IsoValue a where #

Minimal complete definition

Nothing

Associated Types

type ToT a :: T #

type ToT a = GValueType (Rep a)

Methods

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

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

Instances

Instances details
IsoValue Void 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT Void :: T #

Methods

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

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

IsoValue ByteString 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT ByteString :: T #

IsoValue NRational Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Associated Types

type ToT NRational :: T #

IsoValue Rational Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Associated Types

type ToT Rational :: T #

IsoValue UnspecifiedError Source # 
Instance details

Defined in Lorentz.Errors

Associated Types

type ToT UnspecifiedError :: T #

IsoValue Never Source # 
Instance details

Defined in Lorentz.Value

Associated Types

type ToT Never :: T #

IsoValue OpenChest Source # 
Instance details

Defined in Lorentz.Value

Associated Types

type ToT OpenChest :: T #

IsoValue ZSNil Source # 
Instance details

Defined in Lorentz.Zip

Associated Types

type ToT ZSNil :: T #

IsoValue MText 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT MText :: T #

IsoValue Operation 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT Operation :: T #

IsoValue EpAddress 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT EpAddress :: T #

IsoValue MyType2 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Instr.Product

Associated Types

type ToT MyType2 :: T #

Methods

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

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

IsoValue MyCompoundType 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Instr.Sum

Associated Types

type ToT MyCompoundType :: T #

Methods

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

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

IsoValue MyEnum 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Instr.Sum

Associated Types

type ToT MyEnum :: T #

Methods

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

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

IsoValue MyType 
Instance details

Defined in Morley.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 Morley.Michelson.Typed.Haskell.Instr.Sum

Associated Types

type ToT MyType' :: T #

Methods

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

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

IsoValue MyTypeWithNamedField 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Instr.Sum

Associated Types

type ToT MyTypeWithNamedField :: T #

Methods

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

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

IsoValue Address 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT Address :: T #

IsoValue TxRollupL2Address 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT TxRollupL2Address :: T #

Methods

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

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

IsoValue ChainId 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT ChainId :: T #

IsoValue Mutez 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT Mutez :: T #

IsoValue Timestamp 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT Timestamp :: T #

IsoValue KeyHash 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT KeyHash :: T #

IsoValue PublicKey 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT PublicKey :: T #

IsoValue Signature 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT Signature :: T #

IsoValue Bls12381Fr 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT Bls12381Fr :: T #

IsoValue Bls12381G1 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT Bls12381G1 :: T #

IsoValue Bls12381G2 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT Bls12381G2 :: T #

IsoValue Chest 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT Chest :: T #

IsoValue ChestKey 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT ChestKey :: T #

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

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT Text :: T #

Methods

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

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

IsoValue Integer 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT Integer :: T #

IsoValue Natural 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT Natural :: T #

IsoValue () 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT () :: T #

Methods

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

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

IsoValue Bool 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT Bool :: T #

Methods

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

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

IsoValue a => IsoValue (Identity a) 
Instance details

Defined in Morley.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 Morley.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 #

IsoValue (FutureContract arg) Source # 
Instance details

Defined in Lorentz.Address

Associated Types

type ToT (FutureContract arg) :: T #

IsoValue (ChestT a) Source # 
Instance details

Defined in Lorentz.Bytes

Associated Types

type ToT (ChestT a) :: T #

Methods

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

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

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

Defined in Lorentz.Bytes

Associated Types

type ToT (OpenChestT a) :: T #

IsoValue (Packed a) Source # 
Instance details

Defined in Lorentz.Bytes

Associated Types

type ToT (Packed a) :: T #

Methods

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

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

IsoValue (TSignature a) Source # 
Instance details

Defined in Lorentz.Bytes

Associated Types

type ToT (TSignature a) :: T #

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

Defined in Lorentz.Entrypoints.Helpers

Associated Types

type ToT (ShouldHaveEntrypoints r) :: T #

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

This instance cannot be implemented, use IsError instance instead.

Instance details

Defined in Lorentz.Errors

Associated Types

type ToT (CustomError tag) :: T #

Methods

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

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

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

Defined in Lorentz.Macro

Associated Types

type ToT (VoidResult r) :: T #

NiceComparable a => IsoValue (Txr1CallParam a) Source # 
Instance details

Defined in Lorentz.Txr1Call

Associated Types

type ToT (Txr1CallParam a) :: T #

IsoValue (UParam entries) Source # 
Instance details

Defined in Lorentz.UParam

Associated Types

type ToT (UParam entries) :: T #

Methods

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

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

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

Defined in Lorentz.Value

Associated Types

type ToT (ReadTicket a) :: T #

WellTyped t => IsoValue (Value t) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT (Value t) :: T #

Methods

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

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

(HasNoOpToT arg, HasNoNestedBigMaps (ToT arg), WellTypedToT arg) => IsoValue (ContractRef arg) 
Instance details

Defined in Morley.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 #

(Comparable (ToT a), IsoValue a) => IsoValue (Ticket a) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT (Ticket a) :: T #

Methods

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

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

IsoValue a => IsoValue (Maybe a) 
Instance details

Defined in Morley.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 [a] 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT [a] :: T #

Methods

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

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

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

Defined in Morley.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 (Fixed p) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT (Fixed p) :: T #

Methods

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

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

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

Defined in Morley.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 #

IsoValue (TAddress p vd) Source # 
Instance details

Defined in Lorentz.Address

Associated Types

type ToT (TAddress p vd) :: T #

Methods

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

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

(NoLambdaCodeIsomorphismError, WellTyped (LorentzCodeIsNotIsomorphicToMichelsonValues :: T)) => IsoValue (inp :-> out) Source # 
Instance details

Defined in Lorentz.Base

Associated Types

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

Methods

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

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

IsoValue (Hash alg a) Source # 
Instance details

Defined in Lorentz.Bytes

Associated Types

type ToT (Hash alg a) :: T #

Methods

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

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

IsoValue (NFixed p) Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Associated Types

type ToT (NFixed p) :: T #

Methods

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

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

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

Defined in Lorentz.Entrypoints.Manual

Associated Types

type ToT (ParameterWrapper deriv cp) :: T #

Methods

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

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

IsoValue (Extensible x) Source # 
Instance details

Defined in Lorentz.Extensible

Associated Types

type ToT (Extensible x) :: T #

(KnownList i, ZipInstr i, ZipInstr o) => IsoValue (WrappedLambda i o) Source # 
Instance details

Defined in Lorentz.Lambda

Associated Types

type ToT (WrappedLambda i o) :: T #

(HasNoOpToT r, HasNoNestedBigMaps (ToT r), WellTypedToT 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 #

(WellTypedToT r, WellTypedToT 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 #

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

Defined in Lorentz.Zip

Associated Types

type ToT (ZippedStackRepr a b) :: T #

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

Defined in Morley.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 a, IsoValue b) => IsoValue (a, b) 
Instance details

Defined in Morley.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) #

NiceComparable td => IsoValue (STicket action td) Source # 
Instance details

Defined in Lorentz.Tickets

Associated Types

type ToT (STicket action td) :: T #

Methods

toVal :: STicket action td -> Value (ToT (STicket action td)) #

fromVal :: Value (ToT (STicket action td)) -> STicket action td #

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

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

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

Methods

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

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

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

Defined in Morley.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 b, IsoValue c) => IsoValue (a, b, c) 
Instance details

Defined in Morley.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 (BigMapId k2 v) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT (BigMapId k2 v) :: T #

Methods

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

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

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

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

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

Methods

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

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

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

Defined in Morley.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 Morley.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 Morley.Michelson.Typed.Haskell.Value

Associated Types

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

Methods

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

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

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

Primitive types

data Integer #

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

Integers are stored in a kind of sign-magnitude form, hence do not expect two's complement form when using bit operations.

If the value is small (fit into an Int), IS constructor is used. Otherwise IP and IN constructors are used to store a BigNat representing respectively the positive or the negative value magnitude.

Invariant: IP and IN are used iff value doesn't fit in IS

Instances

Instances details
Structured Integer 
Instance details

Defined in Distribution.Utils.Structured

FiniteBitsBase Integer 
Instance details

Defined in Data.Word.Odd

Methods

subWordClz :: Int -> Integer -> Int #

subWordCtz :: Int -> Integer -> Int #

FromJSON TezosBigNum 
Instance details

Defined in Morley.Micheline.Json

Methods

parseJSON :: Value -> Parser TezosBigNum #

parseJSONList :: Value -> Parser [TezosBigNum] #

ToJSON TezosBigNum 
Instance details

Defined in Morley.Micheline.Json

Methods

toJSON :: TezosBigNum -> Value #

toEncoding :: TezosBigNum -> Encoding #

toJSONList :: [TezosBigNum] -> Value #

toEncodingList :: [TezosBigNum] -> Encoding #

ToJSON Integer 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Integer 
Instance details

Defined in Data.Aeson.Types.ToJSON

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 #

Enum Integer

Since: base-2.1

Instance details

Defined in GHC.Enum

Num Integer

Since: base-2.1

Instance details

Defined in GHC.Num

Read Integer

Since: base-2.1

Instance details

Defined in GHC.Read

Integral Integer

Since: base-2.0.1

Instance details

Defined in GHC.Real

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

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 #

NFData Integer 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Integer -> () #

Buildable Integer 
Instance details

Defined in Formatting.Buildable

Methods

build :: Integer -> Builder #

Eq Integer 
Instance details

Defined in GHC.Num.Integer

Methods

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

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

Ord Integer 
Instance details

Defined in GHC.Num.Integer

Hashable Integer 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Integer -> Int #

hash :: Integer -> Int #

HasAnnotation Integer Source # 
Instance details

Defined in Lorentz.Annotation

LDefault Integer Source # 
Instance details

Defined in Lorentz.Default

Methods

ldef :: Integer Source #

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

NonZero Integer Source # 
Instance details

Defined in Lorentz.Macro

Methods

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

HasRPCRepr Integer 
Instance details

Defined in Morley.AsRPC

Associated Types

type AsRPC Integer

TypeHasDoc Integer 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions Integer :: FieldDescriptions #

IsoValue Integer 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT Integer :: T #

HasCLReader Integer 
Instance details

Defined in Morley.Util.CLI

UniformRange Integer 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Integer, Integer) -> g -> m Integer #

Ring Integer 
Instance details

Defined in Data.Semiring

Methods

negate :: Integer -> Integer #

Semiring Integer 
Instance details

Defined in Data.Semiring

Pretty Integer 
Instance details

Defined in Text.PrettyPrint.Leijen.Text

Methods

pretty :: Integer -> Doc #

prettyList :: [Integer] -> Doc #

UnaryArithOpHs Abs Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Abs Integer Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Integer ': s) :-> (UnaryArithResHs Abs Integer ': s) Source #

UnaryArithOpHs Eq' Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Eq' Integer Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Integer ': s) :-> (UnaryArithResHs Eq' Integer ': s) Source #

UnaryArithOpHs Ge Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Ge Integer Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Integer ': s) :-> (UnaryArithResHs Ge Integer ': s) Source #

UnaryArithOpHs Gt Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Gt Integer Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Integer ': s) :-> (UnaryArithResHs Gt Integer ': s) Source #

UnaryArithOpHs Le Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Le Integer Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Integer ': s) :-> (UnaryArithResHs Le Integer ': s) Source #

UnaryArithOpHs Lt Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Lt Integer Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Integer ': s) :-> (UnaryArithResHs Lt Integer ': s) Source #

UnaryArithOpHs Neg Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Neg Integer Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Integer ': s) :-> (UnaryArithResHs Neg Integer ': s) Source #

UnaryArithOpHs Neq Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Neq Integer Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Integer ': s) :-> (UnaryArithResHs Neq Integer ': s) Source #

UnaryArithOpHs Not Integer Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Not Integer Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Integer ': s) :-> (UnaryArithResHs Not Integer ': s) Source #

MultiplyPoint Integer Bls12381G1 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

MultiplyPoint Integer Bls12381G2 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

Lift Integer 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Integer -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Integer -> Code m Integer #

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

Defined in Data.Reflection

Methods

reflect :: proxy n -> Integer #

r ~ Rational => ArithOpHs Div NRational Integer r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (NRational ': (Integer ': s)) :-> (r ': s) Source #

r ~ Rational => ArithOpHs Div Rational Integer r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Rational ': (Integer ': s)) :-> (r ': s) Source #

r ~ Rational => ArithOpHs Div Integer NRational r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (NRational ': s)) :-> (r ': s) Source #

r ~ Rational => ArithOpHs Div Integer Rational r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Rational ': s)) :-> (r ': s) Source #

r ~ Rational => ArithOpHs Add NRational Integer r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (NRational ': (Integer ': s)) :-> (r ': s) Source #

r ~ Rational => ArithOpHs Add Rational Integer r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Rational ': (Integer ': s)) :-> (r ': s) Source #

r ~ Timestamp => ArithOpHs Add Timestamp Integer r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Timestamp ': (Integer ': s)) :-> (r ': s) Source #

r ~ Rational => ArithOpHs Add Integer NRational r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (NRational ': s)) :-> (r ': s) Source #

r ~ Rational => ArithOpHs Add Integer Rational r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Rational ': s)) :-> (r ': s) Source #

r ~ Timestamp => ArithOpHs Add Integer Timestamp r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Timestamp ': s)) :-> (r ': s) Source #

r ~ Integer => ArithOpHs Add Integer Integer r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Integer ': s)) :-> (r ': s) Source #

r ~ Integer => ArithOpHs Add Integer Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Natural ': s)) :-> (r ': s) Source #

r ~ Integer => ArithOpHs Add Natural Integer r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Integer ': s)) :-> (r ': s) Source #

r ~ Natural => ArithOpHs And Integer Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Natural ': s)) :-> (r ': s) Source #

r ~ Maybe (Integer, Natural) => ArithOpHs EDiv Integer Integer r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Integer ': s)) :-> (r ': s) Source #

r ~ Maybe (Integer, Natural) => ArithOpHs EDiv Integer Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Natural ': s)) :-> (r ': s) Source #

r ~ Maybe (Integer, Natural) => ArithOpHs EDiv Natural Integer r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Integer ': s)) :-> (r ': s) Source #

r ~ Rational => ArithOpHs Mul NRational Integer r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (NRational ': (Integer ': s)) :-> (r ': s) Source #

r ~ Rational => ArithOpHs Mul Rational Integer r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Rational ': (Integer ': s)) :-> (r ': s) Source #

r ~ Bls12381Fr => ArithOpHs Mul Bls12381Fr Integer r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Bls12381Fr ': (Integer ': s)) :-> (r ': s) Source #

r ~ Rational => ArithOpHs Mul Integer NRational r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (NRational ': s)) :-> (r ': s) Source #

r ~ Rational => ArithOpHs Mul Integer Rational r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Rational ': s)) :-> (r ': s) Source #

r ~ Bls12381Fr => ArithOpHs Mul Integer Bls12381Fr r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Bls12381Fr ': s)) :-> (r ': s) Source #

r ~ Integer => ArithOpHs Mul Integer Integer r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Integer ': s)) :-> (r ': s) Source #

r ~ Integer => ArithOpHs Mul Integer Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Natural ': s)) :-> (r ': s) Source #

r ~ Integer => ArithOpHs Mul Natural Integer r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Integer ': s)) :-> (r ': s) Source #

r ~ Rational => ArithOpHs Sub NRational Integer r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (NRational ': (Integer ': s)) :-> (r ': s) Source #

r ~ Rational => ArithOpHs Sub Rational Integer r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Rational ': (Integer ': s)) :-> (r ': s) Source #

r ~ Timestamp => ArithOpHs Sub Timestamp Integer r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Timestamp ': (Integer ': s)) :-> (r ': s) Source #

r ~ Rational => ArithOpHs Sub Integer NRational r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (NRational ': s)) :-> (r ': s) Source #

r ~ Rational => ArithOpHs Sub Integer Rational r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Rational ': s)) :-> (r ': s) Source #

r ~ Integer => ArithOpHs Sub Integer Integer r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Integer ': s)) :-> (r ': s) Source #

r ~ Integer => ArithOpHs Sub Integer Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Natural ': s)) :-> (r ': s) Source #

r ~ Integer => ArithOpHs Sub Natural Integer r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Integer ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Add Integer (Fixed p) r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Fixed p ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Add Integer (NFixed p) r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (NFixed p ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Mul Integer (Fixed p) r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Fixed p ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Mul Integer (NFixed p) r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (NFixed p ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Sub Integer (Fixed p) r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Fixed p ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Sub Integer (NFixed p) r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (NFixed p ': s)) :-> (r ': s) Source #

() :=> (Bits Integer) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Bits Integer #

() :=> (Enum Integer) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Enum Integer #

() :=> (Num Integer) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Num Integer #

() :=> (Integral Integer) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Integral Integer #

() :=> (Real Integer) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Real Integer #

() :=> (Eq Integer) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Eq Integer #

() :=> (Ord Integer) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Ord Integer #

r ~ Fixed p => ArithOpHs Add (Fixed p) Integer r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Fixed p ': (Integer ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Add (NFixed p) Integer r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (NFixed p ': (Integer ': s)) :-> (r ': s) Source #

(r ~ Maybe (Integer, NFixed (BinBase a)), KnownNat a) => ArithOpHs EDiv (Fixed (BinBase a)) Integer r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Fixed (BinBase a) ': (Integer ': s)) :-> (r ': s) Source #

(r ~ Maybe (Integer, NFixed (DecBase a)), KnownNat a) => ArithOpHs EDiv (Fixed (DecBase a)) Integer r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Fixed (DecBase a) ': (Integer ': s)) :-> (r ': s) Source #

(r ~ Maybe (Integer, NFixed (BinBase a)), KnownNat a) => ArithOpHs EDiv (NFixed (BinBase a)) Integer r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (NFixed (BinBase a) ': (Integer ': s)) :-> (r ': s) Source #

(r ~ Maybe (Integer, NFixed (DecBase a)), KnownNat a) => ArithOpHs EDiv (NFixed (DecBase a)) Integer r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (NFixed (DecBase a) ': (Integer ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Mul (Fixed p) Integer r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Fixed p ': (Integer ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Mul (NFixed p) Integer r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (NFixed p ': (Integer ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Sub (Fixed p) Integer r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Fixed p ': (Integer ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Sub (NFixed p) Integer r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (NFixed p ': (Integer ': s)) :-> (r ': s) Source #

type Difference Integer 
Instance details

Defined in Basement.Numerical.Subtractive

type IntBaseType Integer 
Instance details

Defined in Data.IntCast

type AsRPC Integer 
Instance details

Defined in Morley.AsRPC

type AsRPC Integer = Integer
type TypeDocFieldDescriptions Integer 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

type ToT Integer 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

type ToT Integer = 'TInt
type PrettyShow Integer 
Instance details

Defined in Morley.Prelude.Show

type PrettyShow Integer = ()
type UnaryArithResHs Abs Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Eq' Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Ge Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Gt Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Le Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Lt Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Neg Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Neq Integer Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Not Integer Source # 
Instance details

Defined in Lorentz.Arith

data Natural #

Natural number

Invariant: numbers <= 0xffffffffffffffff use the NS constructor

Instances

Instances details
FromJSON TezosNat 
Instance details

Defined in Morley.Micheline.Json

Methods

parseJSON :: Value -> Parser TezosNat #

parseJSONList :: Value -> Parser [TezosNat] #

ToJSON TezosNat 
Instance details

Defined in Morley.Micheline.Json

Methods

toJSON :: TezosNat -> Value #

toEncoding :: TezosNat -> Encoding #

toJSONList :: [TezosNat] -> Value #

toEncodingList :: [TezosNat] -> Encoding #

ToJSON Natural 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Natural 
Instance details

Defined in Data.Aeson.Types.ToJSON

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 #

Enum Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Enum

Num Natural

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

Since: base-4.8.0.0

Instance details

Defined in GHC.Num

Read Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Read

Integral Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Real

Real Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Real

Show Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Show

Subtractive Natural 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Natural #

NFData Natural

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Natural -> () #

Buildable TezosNat 
Instance details

Defined in Morley.Micheline.Json

Methods

build :: TezosNat -> Builder #

Eq Natural 
Instance details

Defined in GHC.Num.Natural

Methods

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

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

Ord Natural 
Instance details

Defined in GHC.Num.Natural

Hashable Natural 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Natural -> Int #

hash :: Natural -> Int #

HasAnnotation Natural Source # 
Instance details

Defined in Lorentz.Annotation

ToIntegerArithOpHs Natural Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalToIntOpHs :: forall (s :: [Type]). (Natural ': s) :-> (Integer ': s) Source #

LDefault Natural Source # 
Instance details

Defined in Lorentz.Default

Methods

ldef :: Natural Source #

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

NonZero Natural Source # 
Instance details

Defined in Lorentz.Macro

Methods

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

HasRPCRepr Natural 
Instance details

Defined in Morley.AsRPC

Associated Types

type AsRPC Natural

TypeHasDoc Natural 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions Natural :: FieldDescriptions #

IsoValue Natural 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT Natural :: T #

HasCLReader Natural 
Instance details

Defined in Morley.Util.CLI

UniformRange Natural 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Natural, Natural) -> g -> m Natural #

Semiring Natural 
Instance details

Defined in Data.Semiring

UnaryArithOpHs Eq' Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Eq' Natural Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Natural ': s) :-> (UnaryArithResHs Eq' Natural ': s) Source #

UnaryArithOpHs Ge Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Ge Natural Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Natural ': s) :-> (UnaryArithResHs Ge Natural ': s) Source #

UnaryArithOpHs Gt Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Gt Natural Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Natural ': s) :-> (UnaryArithResHs Gt Natural ': s) Source #

UnaryArithOpHs Le Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Le Natural Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Natural ': s) :-> (UnaryArithResHs Le Natural ': s) Source #

UnaryArithOpHs Lt Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Lt Natural Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Natural ': s) :-> (UnaryArithResHs Lt Natural ': s) Source #

UnaryArithOpHs Neg Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Neg Natural Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Natural ': s) :-> (UnaryArithResHs Neg Natural ': s) Source #

UnaryArithOpHs Neq Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Neq Natural Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Natural ': s) :-> (UnaryArithResHs Neq Natural ': s) Source #

UnaryArithOpHs Not Natural Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Not Natural Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Natural ': s) :-> (UnaryArithResHs Not Natural ': s) Source #

Lift Natural 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Natural -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Natural -> Code m Natural #

r ~ NRational => ArithOpHs Div NRational Natural r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (NRational ': (Natural ': s)) :-> (r ': s) Source #

r ~ Rational => ArithOpHs Div Rational Natural r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Rational ': (Natural ': s)) :-> (r ': s) Source #

r ~ NRational => ArithOpHs Div Natural NRational r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (NRational ': s)) :-> (r ': s) Source #

r ~ Rational => ArithOpHs Div Natural Rational r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Rational ': s)) :-> (r ': s) Source #

r ~ NRational => ArithOpHs Add NRational Natural r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (NRational ': (Natural ': s)) :-> (r ': s) Source #

r ~ Rational => ArithOpHs Add Rational Natural r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Rational ': (Natural ': s)) :-> (r ': s) Source #

r ~ Integer => ArithOpHs Add Integer Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Natural ': s)) :-> (r ': s) Source #

r ~ NRational => ArithOpHs Add Natural NRational r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (NRational ': s)) :-> (r ': s) Source #

r ~ Rational => ArithOpHs Add Natural Rational r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Rational ': s)) :-> (r ': s) Source #

r ~ Integer => ArithOpHs Add Natural Integer r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Integer ': s)) :-> (r ': s) Source #

r ~ Natural => ArithOpHs Add Natural Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Natural ': s)) :-> (r ': s) Source #

r ~ Natural => ArithOpHs And Integer Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Natural ': s)) :-> (r ': s) Source #

r ~ Natural => ArithOpHs And Natural Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Natural ': s)) :-> (r ': s) Source #

r ~ Maybe (Mutez, Mutez) => ArithOpHs EDiv Mutez Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Mutez ': (Natural ': s)) :-> (r ': s) Source #

r ~ Maybe (Integer, Natural) => ArithOpHs EDiv Integer Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Natural ': s)) :-> (r ': s) Source #

r ~ Maybe (Integer, Natural) => ArithOpHs EDiv Natural Integer r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Integer ': s)) :-> (r ': s) Source #

r ~ Maybe (Natural, Natural) => ArithOpHs EDiv Natural Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Natural ': s)) :-> (r ': s) Source #

r ~ Natural => ArithOpHs Lsl Natural Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Natural ': s)) :-> (r ': s) Source #

r ~ Natural => ArithOpHs Lsr Natural Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Natural ': s)) :-> (r ': s) Source #

r ~ NRational => ArithOpHs Mul NRational Natural r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (NRational ': (Natural ': s)) :-> (r ': s) Source #

r ~ Rational => ArithOpHs Mul Rational Natural r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Rational ': (Natural ': s)) :-> (r ': s) Source #

r ~ Mutez => ArithOpHs Mul Mutez Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Mutez ': (Natural ': s)) :-> (r ': s) Source #

r ~ Bls12381Fr => ArithOpHs Mul Bls12381Fr Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Bls12381Fr ': (Natural ': s)) :-> (r ': s) Source #

r ~ Integer => ArithOpHs Mul Integer Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Natural ': s)) :-> (r ': s) Source #

r ~ NRational => ArithOpHs Mul Natural NRational r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (NRational ': s)) :-> (r ': s) Source #

r ~ Rational => ArithOpHs Mul Natural Rational r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Rational ': s)) :-> (r ': s) Source #

r ~ Mutez => ArithOpHs Mul Natural Mutez r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Mutez ': s)) :-> (r ': s) Source #

r ~ Bls12381Fr => ArithOpHs Mul Natural Bls12381Fr r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Bls12381Fr ': s)) :-> (r ': s) Source #

r ~ Integer => ArithOpHs Mul Natural Integer r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Integer ': s)) :-> (r ': s) Source #

r ~ Natural => ArithOpHs Mul Natural Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Natural ': s)) :-> (r ': s) Source #

r ~ Natural => ArithOpHs Or Natural Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Natural ': s)) :-> (r ': s) Source #

r ~ Rational => ArithOpHs Sub NRational Natural r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (NRational ': (Natural ': s)) :-> (r ': s) Source #

r ~ Rational => ArithOpHs Sub Rational Natural r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Rational ': (Natural ': s)) :-> (r ': s) Source #

r ~ Integer => ArithOpHs Sub Integer Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Natural ': s)) :-> (r ': s) Source #

r ~ Rational => ArithOpHs Sub Natural NRational r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (NRational ': s)) :-> (r ': s) Source #

r ~ Rational => ArithOpHs Sub Natural Rational r Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Rational ': s)) :-> (r ': s) Source #

r ~ Integer => ArithOpHs Sub Natural Integer r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Integer ': s)) :-> (r ': s) Source #

r ~ Integer => ArithOpHs Sub Natural Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Natural ': s)) :-> (r ': s) Source #

r ~ Natural => ArithOpHs Xor Natural Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Natural ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Add Natural (Fixed p) r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Fixed p ': s)) :-> (r ': s) Source #

r ~ NFixed p => ArithOpHs Add Natural (NFixed p) r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (NFixed p ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Mul Natural (Fixed p) r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Fixed p ': s)) :-> (r ': s) Source #

r ~ NFixed p => ArithOpHs Mul Natural (NFixed p) r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (NFixed p ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Sub Natural (Fixed p) r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Fixed p ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Sub Natural (NFixed p) r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (NFixed p ': s)) :-> (r ': s) Source #

() :=> (Bits Natural) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Bits Natural #

() :=> (Enum Natural) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Enum Natural #

() :=> (Num Natural) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Num Natural #

() :=> (Read Natural) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Read Natural #

() :=> (Integral Natural) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Integral 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 #

() :=> (Eq Natural) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Eq Natural #

() :=> (Ord Natural) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Ord Natural #

r ~ Fixed p => ArithOpHs Add (Fixed p) Natural r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Fixed p ': (Natural ': s)) :-> (r ': s) Source #

r ~ NFixed p => ArithOpHs Add (NFixed p) Natural r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (NFixed p ': (Natural ': s)) :-> (r ': s) Source #

(r ~ Maybe (Integer, NFixed (BinBase a)), KnownNat a) => ArithOpHs EDiv (Fixed (BinBase a)) Natural r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Fixed (BinBase a) ': (Natural ': s)) :-> (r ': s) Source #

(r ~ Maybe (Integer, NFixed (DecBase a)), KnownNat a) => ArithOpHs EDiv (Fixed (DecBase a)) Natural r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Fixed (DecBase a) ': (Natural ': s)) :-> (r ': s) Source #

(r ~ Maybe (Natural, NFixed (BinBase a)), KnownNat a) => ArithOpHs EDiv (NFixed (BinBase a)) Natural r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (NFixed (BinBase a) ': (Natural ': s)) :-> (r ': s) Source #

(r ~ Maybe (Natural, NFixed (DecBase a)), KnownNat a) => ArithOpHs EDiv (NFixed (DecBase a)) Natural r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (NFixed (DecBase a) ': (Natural ': s)) :-> (r ': s) Source #

r ~ NFixed (BinBase b) => ArithOpHs Lsl (NFixed (BinBase a)) Natural r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (NFixed (BinBase a) ': (Natural ': s)) :-> (r ': s) Source #

r ~ NFixed (BinBase b) => ArithOpHs Lsr (NFixed (BinBase a)) Natural r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (NFixed (BinBase a) ': (Natural ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Mul (Fixed p) Natural r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Fixed p ': (Natural ': s)) :-> (r ': s) Source #

r ~ NFixed p => ArithOpHs Mul (NFixed p) Natural r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (NFixed p ': (Natural ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Sub (Fixed p) Natural r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Fixed p ': (Natural ': s)) :-> (r ': s) Source #

r ~ Fixed p => ArithOpHs Sub (NFixed p) Natural r Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (NFixed p ': (Natural ': s)) :-> (r ': s) Source #

type Difference Natural 
Instance details

Defined in Basement.Numerical.Subtractive

type IntBaseType Natural 
Instance details

Defined in Data.IntCast

type AsRPC Natural 
Instance details

Defined in Morley.AsRPC

type AsRPC Natural = Natural
type TypeDocFieldDescriptions Natural 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

type ToT Natural 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

type ToT Natural = 'TNat
type PrettyShow Natural 
Instance details

Defined in Morley.Prelude.Show

type PrettyShow Natural = ()
type UnaryArithResHs Eq' Natural Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Ge Natural Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Gt Natural Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Le Natural Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Lt Natural Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Neg Natural Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Neq Natural Source # 
Instance details

Defined in Lorentz.Arith

type UnaryArithResHs Not Natural Source # 
Instance details

Defined in Lorentz.Arith

data MText #

Instances

Instances details
FromJSON MText 
Instance details

Defined in Morley.Michelson.Text

ToJSON MText 
Instance details

Defined in Morley.Michelson.Text

Data MText 
Instance details

Defined in Morley.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 #

Monoid MText 
Instance details

Defined in Morley.Michelson.Text

Methods

mempty :: MText #

mappend :: MText -> MText -> MText #

mconcat :: [MText] -> MText #

Semigroup MText 
Instance details

Defined in Morley.Michelson.Text

Methods

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

sconcat :: NonEmpty MText -> MText #

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

Generic MText 
Instance details

Defined in Morley.Michelson.Text

Associated Types

type Rep MText :: Type -> Type #

Methods

from :: MText -> Rep MText x #

to :: Rep MText x -> MText #

Show MText 
Instance details

Defined in Morley.Michelson.Text

Methods

showsPrec :: Int -> MText -> ShowS #

show :: MText -> String #

showList :: [MText] -> ShowS #

NFData MText 
Instance details

Defined in Morley.Michelson.Text

Methods

rnf :: MText -> () #

Buildable MText 
Instance details

Defined in Morley.Michelson.Text

Methods

build :: MText -> Builder #

Eq MText 
Instance details

Defined in Morley.Michelson.Text

Methods

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

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

Ord MText 
Instance details

Defined in Morley.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 #

Hashable MText 
Instance details

Defined in Morley.Michelson.Text

Methods

hashWithSalt :: Int -> MText -> Int #

hash :: MText -> Int #

HasAnnotation MText Source # 
Instance details

Defined in Lorentz.Annotation

ErrorHasDoc MText Source # 
Instance details

Defined in Lorentz.Errors

Associated Types

type ErrorRequirements MText Source #

IsCustomErrorArgRep MText Source # 
Instance details

Defined in Lorentz.Errors

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). SingI t => Value t -> Either Text MText Source #

failUsing :: forall (s :: [Type]) (t :: [Type]). IsError MText => MText -> s :-> t Source #

ConcatOpHs MText Source # 
Instance details

Defined in Lorentz.Polymorphic

SizeOpHs MText Source # 
Instance details

Defined in Lorentz.Polymorphic

SliceOpHs MText Source # 
Instance details

Defined in Lorentz.Polymorphic

HasRPCRepr MText 
Instance details

Defined in Morley.AsRPC

Associated Types

type AsRPC MText

TypeHasDoc MText 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions MText :: FieldDescriptions #

IsoValue MText 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT MText :: T #

HasCLReader MText 
Instance details

Defined in Morley.Michelson.Text

Container MText 
Instance details

Defined in Morley.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 #

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

fold :: MText -> Element MText #

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

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

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

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

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

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

ToText MText 
Instance details

Defined in Morley.Michelson.Text

Methods

toText :: MText -> Text #

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

Defined in Lorentz.Errors

type Rep MText 
Instance details

Defined in Morley.Michelson.Text

type Rep MText = D1 ('MetaData "MText" "Morley.Michelson.Text" "morley-1.19.0-inplace" 'True) (C1 ('MetaCons "UnsafeMText" 'PrefixI 'True) (S1 ('MetaSel ('Just "unMText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))
type ErrorRequirements MText Source # 
Instance details

Defined in Lorentz.Errors

type AsRPC MText 
Instance details

Defined in Morley.AsRPC

type AsRPC MText = MText
type TypeDocFieldDescriptions MText 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

type ToT MText 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

type ToT MText = 'TString
type Element MText 
Instance details

Defined in Morley.Michelson.Text

data Bool #

Constructors

False 
True 

Instances

Instances details
Structured Bool 
Instance details

Defined in Distribution.Utils.Structured

ToJSON Bool 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Bool 
Instance details

Defined in Data.Aeson.Types.ToJSON

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 #

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

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

Generic Bool 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Bool :: Type -> Type #

Methods

from :: Bool -> Rep Bool x #

to :: Rep Bool x -> Bool #

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

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 #

BitOps Bool 
Instance details

Defined in Basement.Bits

FiniteBitsOps Bool 
Instance details

Defined in Basement.Bits

NFData Bool 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Bool -> () #

Buildable Bool 
Instance details

Defined in Formatting.Buildable

Methods

build :: Bool -> Builder #

Eq Bool 
Instance details

Defined in GHC.Classes

Methods

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

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

Ord Bool 
Instance details

Defined in GHC.Classes

Methods

compare :: Bool -> Bool -> Ordering #

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

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

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

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

max :: Bool -> Bool -> Bool #

min :: Bool -> Bool -> Bool #

Hashable Bool 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Bool -> Int #

hash :: Bool -> Int #

HasAnnotation Bool Source # 
Instance details

Defined in Lorentz.Annotation

HasRPCRepr Bool 
Instance details

Defined in Morley.AsRPC

Associated Types

type AsRPC Bool

TypeHasDoc Bool 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions Bool :: FieldDescriptions #

IsoValue Bool 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT Bool :: T #

Methods

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

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

Boolean Bool 
Instance details

Defined in Morley.Prelude.Boolean

Methods

(&&) :: Bool -> Bool -> Bool

(||) :: Bool -> Bool -> Bool

Uniform Bool 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Bool #

UniformRange Bool 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Bool, Bool) -> g -> m Bool #

Semiring Bool 
Instance details

Defined in Data.Semiring

Methods

plus :: Bool -> Bool -> Bool #

zero :: Bool #

times :: Bool -> Bool -> Bool #

one :: Bool #

fromNatural :: Natural -> Bool #

PEq Bool 
Instance details

Defined in Data.Eq.Singletons

Associated Types

type arg == arg1 :: Bool #

type arg /= arg1 :: Bool #

SEq Bool 
Instance details

Defined in Data.Eq.Singletons

Methods

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

POrd Bool 
Instance details

Defined in Data.Ord.Singletons

Associated Types

type Compare arg arg1 :: Ordering #

type arg < arg1 :: Bool #

type arg <= arg1 :: Bool #

type arg > arg1 :: Bool #

type arg >= arg1 :: Bool #

type Max arg arg1 :: a #

type Min arg arg1 :: a #

SOrd Bool 
Instance details

Defined in Data.Ord.Singletons

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

PBounded Bool 
Instance details

Defined in Data.Singletons.Base.Enum

Associated Types

type MinBound :: a #

type MaxBound :: a #

PEnum Bool 
Instance details

Defined in Data.Singletons.Base.Enum

Associated Types

type Succ arg :: a #

type Pred arg :: a #

type ToEnum arg :: a #

type FromEnum arg :: Nat #

type EnumFromTo arg arg1 :: [a] #

type EnumFromThenTo arg arg1 arg2 :: [a] #

SBounded Bool 
Instance details

Defined in Data.Singletons.Base.Enum

SEnum Bool 
Instance details

Defined in Data.Singletons.Base.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) #

PShow Bool 
Instance details

Defined in Text.Show.Singletons

Associated Types

type ShowsPrec arg arg1 arg2 :: Symbol #

type Show_ arg :: Symbol #

type ShowList arg arg1 :: Symbol #

SShow Bool 
Instance details

Defined in Text.Show.Singletons

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

Unbox Bool 
Instance details

Defined in Data.Vector.Unboxed.Base

Pretty Bool 
Instance details

Defined in Text.PrettyPrint.Leijen.Text

Methods

pretty :: Bool -> Doc #

prettyList :: [Bool] -> Doc #

TestCoercion SBool 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

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

TestEquality SBool 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

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

SingI 'False

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing 'False

SingI 'True

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing 'True

UnaryArithOpHs Not Bool Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Not Bool Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Bool ': s) :-> (UnaryArithResHs Not Bool ': s) Source #

Lift Bool 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Bool -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Bool -> Code m Bool #

Vector Vector Bool 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Bool 
Instance details

Defined in Data.Vector.Unboxed.Base

r ~ Bool => ArithOpHs And Bool Bool r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Bool ': (Bool ': s)) :-> (r ': s) Source #

r ~ Bool => ArithOpHs Or Bool Bool r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Bool ': (Bool ': s)) :-> (r ': s) Source #

r ~ Bool => ArithOpHs Xor Bool Bool r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Bool ': (Bool ': s)) :-> (r ': s) Source #

() :=> (Bits Bool) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Bits Bool #

() :=> (Bounded Bool) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Bounded Bool #

() :=> (Enum Bool) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Enum 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 #

() :=> (Eq Bool) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Eq Bool #

() :=> (Ord Bool) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Ord Bool #

SingI GetAllSym0 
Instance details

Defined in Data.Semigroup.Singletons.Internal

Methods

sing :: Sing GetAllSym0 #

SingI GetAnySym0 
Instance details

Defined in Data.Semigroup.Singletons.Internal

Methods

sing :: Sing GetAnySym0 #

SingI AllSym0 
Instance details

Defined in Data.Semigroup.Singletons.Internal

Methods

sing :: Sing AllSym0 #

SingI All_Sym0 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Disambiguation

Methods

sing :: Sing All_Sym0 #

SingI AnySym0 
Instance details

Defined in Data.Semigroup.Singletons.Internal

Methods

sing :: Sing AnySym0 #

SingI Any_Sym0 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Disambiguation

Methods

sing :: Sing Any_Sym0 #

SingI ShowParenSym0 
Instance details

Defined in Text.Show.Singletons

SingI AndSym0 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing AndSym0 #

SingI OrSym0 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing OrSym0 #

SingI ContainsBigMapSym 
Instance details

Defined in Morley.Michelson.Typed.Scope

Methods

sing :: Sing ContainsBigMapSym #

SingI ContainsContractSym 
Instance details

Defined in Morley.Michelson.Typed.Scope

Methods

sing :: Sing ContainsContractSym #

SingI ContainsNestedBigMapsSym 
Instance details

Defined in Morley.Michelson.Typed.Scope

Methods

sing :: Sing ContainsNestedBigMapsSym #

SingI ContainsOpSym 
Instance details

Defined in Morley.Michelson.Typed.Scope

Methods

sing :: Sing ContainsOpSym #

SingI ContainsTicketSym 
Instance details

Defined in Morley.Michelson.Typed.Scope

Methods

sing :: Sing ContainsTicketSym #

SingI (&&@#@$) 
Instance details

Defined in Data.Bool.Singletons

Methods

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

SingI (||@#@$) 
Instance details

Defined in Data.Bool.Singletons

Methods

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

SingI NotSym0 
Instance details

Defined in Data.Bool.Singletons

Methods

sing :: Sing NotSym0 #

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

Defined in GHC.TypeLits.Singletons.Internal

Methods

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

SuppressUnusedWarnings TFHelper_6989586621679606123Sym0 
Instance details

Defined in Data.Semigroup.Singletons.Internal

SuppressUnusedWarnings GetAllSym0 
Instance details

Defined in Data.Semigroup.Singletons.Internal

SuppressUnusedWarnings TFHelper_6989586621679606140Sym0 
Instance details

Defined in Data.Semigroup.Singletons.Internal

SuppressUnusedWarnings GetAnySym0 
Instance details

Defined in Data.Semigroup.Singletons.Internal

SuppressUnusedWarnings TFHelper_6989586621679130639Sym0 
Instance details

Defined in Data.Eq.Singletons

SuppressUnusedWarnings TFHelper_6989586621679131028Sym0 
Instance details

Defined in Data.Eq.Singletons

SuppressUnusedWarnings TFHelper_6989586621679131037Sym0 
Instance details

Defined in Data.Eq.Singletons

SuppressUnusedWarnings AllSym0 
Instance details

Defined in Data.Semigroup.Singletons.Internal

SuppressUnusedWarnings All_Sym0 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Disambiguation

SuppressUnusedWarnings AnySym0 
Instance details

Defined in Data.Semigroup.Singletons.Internal

SuppressUnusedWarnings Any_Sym0 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Disambiguation

SuppressUnusedWarnings ShowParenSym0 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings Compare_6989586621679181840Sym0 
Instance details

Defined in Data.Ord.Singletons

SuppressUnusedWarnings (&&@#@$) 
Instance details

Defined in Data.Bool.Singletons

SuppressUnusedWarnings (||@#@$) 
Instance details

Defined in Data.Bool.Singletons

SuppressUnusedWarnings TFHelper_6989586621679131019Sym0 
Instance details

Defined in Data.Eq.Singletons

SuppressUnusedWarnings NotSym0 
Instance details

Defined in Data.Bool.Singletons

SuppressUnusedWarnings FromEnum_6989586621679544301Sym0 
Instance details

Defined in Data.Singletons.Base.Enum

SuppressUnusedWarnings ShowsPrec_6989586621680071834Sym0 
Instance details

Defined in Text.Show.Singletons

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

Defined in GHC.TypeLits.Singletons.Internal

SuppressUnusedWarnings ToEnum_6989586621679544288Sym0 
Instance details

Defined in Data.Singletons.Base.Enum

SuppressUnusedWarnings AndSym0 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings OrSym0 
Instance details

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing NubBySym0 #

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

Defined in Data.List.Singletons.Internal.Disambiguation

Methods

sing :: Sing ListnubBySym0 #

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

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing Elem_bySym0 #

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

Defined in Data.List.Singletons.Internal

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

Defined in GHC.Base.Singletons

Methods

sing :: Sing UntilSym0 #

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing FindSym0 #

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

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing BreakSym0 #

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing SpanSym0 #

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

Defined in Data.List.Singletons.Internal.Disambiguation

Methods

sing :: Sing ListpartitionSym0 #

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

Defined in Data.List.Singletons.Internal.Disambiguation

Methods

sing :: Sing ListspanSym0 #

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

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing AllSym0 #

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

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing AnySym0 #

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing FilterSym0 #

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal.Disambiguation

Methods

sing :: Sing ListdropWhileSym0 #

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

Defined in Data.List.Singletons.Internal.Disambiguation

Methods

sing :: Sing ListfilterSym0 #

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

Defined in Data.List.Singletons.Internal.Disambiguation

Methods

sing :: Sing ListtakeWhileSym0 #

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

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing SelectSym0 #

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

Defined in Data.Maybe.Singletons

Methods

sing :: Sing IsJustSym0 #

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

Defined in Data.Maybe.Singletons

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

Defined in Control.Monad.Singletons

Methods

sing :: Sing UnlessSym0 #

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

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing WhenSym0 #

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

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing GuardSym0 #

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal.Disambiguation

Methods

sing :: Sing ListisPrefixOfSym0 #

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

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing NullSym0 #

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

Defined in Data.List.Singletons.Internal.Disambiguation

Methods

sing :: Sing ListnullSym0 #

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

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing ElemSym0 #

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

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing NotElemSym0 #

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

Defined in Data.List.Singletons.Internal.Disambiguation

Methods

sing :: Sing ListelemSym0 #

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

Defined in Data.Bool.Singletons

Methods

sing :: Sing Bool_Sym0 #

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

Defined in Data.Eq.Singletons

Methods

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

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

Defined in Data.Eq.Singletons

Methods

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

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

Defined in Data.Ord.Singletons

Methods

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

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

Defined in Data.Ord.Singletons

Methods

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

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

Defined in Data.Ord.Singletons

Methods

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

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

Defined in Data.Ord.Singletons

Methods

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

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

Defined in Data.Foldable.Singletons

Methods

sing :: Sing AndSym0 #

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

Defined in Data.Foldable.Singletons

Methods

sing :: Sing OrSym0 #

SingI (IfSym0 :: TyFun Bool (k ~> (k ~> k)) -> Type) 
Instance details

Defined in Data.Bool.Singletons

Methods

sing :: Sing IfSym0 #

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

Defined in Data.Bool.Singletons

Methods

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

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

Defined in Data.Bool.Singletons

Methods

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

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

Defined in GHC.TypeLits.Singletons.Internal

Methods

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

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

Defined in Data.Eq.Singletons

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

Defined in Data.Functor.Identity.Singletons

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

Defined in Data.Monoid.Singletons

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

Defined in Data.Monoid.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Semigroup.Singletons.Internal

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

Defined in Data.Semigroup.Singletons.Internal

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

Defined in Data.Semigroup.Singletons.Internal

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

Defined in Data.Semigroup.Singletons.Internal

SuppressUnusedWarnings (TFHelper_6989586621679606280Sym0 :: TyFun (WrappedMonoid m) (WrappedMonoid m ~> Bool) -> Type) 
Instance details

Defined in Data.Semigroup.Singletons.Internal

SuppressUnusedWarnings (TFHelper_6989586621679606123Sym1 a6989586621679606128 :: TyFun All Bool -> Type) 
Instance details

Defined in Data.Semigroup.Singletons.Internal

SuppressUnusedWarnings (TFHelper_6989586621679606140Sym1 a6989586621679606145 :: TyFun Any Bool -> Type) 
Instance details

Defined in Data.Semigroup.Singletons.Internal

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

Defined in Data.Semigroup.Singletons.Internal

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Semigroup.Singletons.Internal

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Semigroup.Singletons.Internal

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

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (TFHelper_6989586621679130639Sym1 a6989586621679130644 :: TyFun Void Bool -> Type) 
Instance details

Defined in Data.Eq.Singletons

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

Defined in Data.Eq.Singletons

SuppressUnusedWarnings (TFHelper_6989586621679131028Sym1 a6989586621679131033 :: TyFun Ordering Bool -> Type) 
Instance details

Defined in Data.Eq.Singletons

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal.Disambiguation

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in GHC.Base.Singletons

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal.Disambiguation

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

Defined in Data.List.Singletons.Internal.Disambiguation

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal.Disambiguation

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

Defined in Data.List.Singletons.Internal.Disambiguation

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

Defined in Data.List.Singletons.Internal.Disambiguation

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.Eq.Singletons

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

Defined in Data.Maybe.Singletons

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

Defined in Data.Maybe.Singletons

SuppressUnusedWarnings (TFHelper_6989586621679131037Sym1 a6989586621679131042 :: TyFun () Bool -> Type) 
Instance details

Defined in Data.Eq.Singletons

SuppressUnusedWarnings (Compare_6989586621679181840Sym1 a6989586621679181845 :: TyFun Bool Ordering -> Type) 
Instance details

Defined in Data.Ord.Singletons

SuppressUnusedWarnings (ShowsPrec_6989586621680071834Sym1 a6989586621680071844 :: TyFun Bool (Symbol ~> Symbol) -> Type) 
Instance details

Defined in Text.Show.Singletons

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

Defined in Control.Monad.Singletons

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

Defined in Control.Monad.Singletons.Internal

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

Defined in Data.Bool.Singletons

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

Defined in Data.Bool.Singletons

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

Defined in Data.Bool.Singletons

SuppressUnusedWarnings (TFHelper_6989586621679131019Sym1 a6989586621679131024 :: TyFun Bool Bool -> Type) 
Instance details

Defined in Data.Eq.Singletons

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

Defined in Control.Monad.Singletons.Internal

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

Defined in GHC.TypeLits.Singletons.Internal

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

Defined in Data.Eq.Singletons

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal.Disambiguation

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

Defined in Data.Foldable.Singletons

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal.Disambiguation

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

Defined in Data.Functor.Identity.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal.Disambiguation

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

Defined in Data.Bool.Singletons

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

Defined in Data.Eq.Singletons

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

Defined in Data.Eq.Singletons

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

Defined in Data.Eq.Singletons

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

Defined in Data.Eq.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Eq.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Proxy.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Either.Singletons

Methods

sing :: Sing IsLeftSym0 #

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

Defined in Data.Either.Singletons

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

Defined in Control.Monad.Singletons

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

Defined in Data.Foldable.Singletons

Methods

sing :: Sing FindSym0 #

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

Defined in Data.Foldable.Singletons

Methods

sing :: Sing AllSym0 #

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

Defined in Data.Foldable.Singletons

Methods

sing :: Sing AnySym0 #

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

Defined in Control.Monad.Singletons

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

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (AllSym1 d) #

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

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (AnySym1 d) #

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

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ElemSym1 d) #

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

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (IsInfixOfSym1 d) #

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

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (IsPrefixOfSym1 d) #

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

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (IsSuffixOfSym1 d) #

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

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (NotElemSym1 d) #

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

Defined in Data.List.Singletons.Internal.Disambiguation

Methods

sing :: Sing (ListelemSym1 d) #

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

Defined in Data.List.Singletons.Internal.Disambiguation

Methods

sing :: Sing (ListisPrefixOfSym1 d) #

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

Defined in Data.Bool.Singletons

Methods

sing :: Sing (Bool_Sym1 d) #

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

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (Elem_bySym1 d) #

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

Defined in Data.Foldable.Singletons

Methods

sing :: Sing ElemSym0 #

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Eq.Singletons

Methods

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

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

Defined in Data.Eq.Singletons

Methods

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

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

Defined in Data.Ord.Singletons

Methods

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

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

Defined in Data.Ord.Singletons

Methods

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

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

Defined in Data.Ord.Singletons

Methods

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

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

Defined in Data.Ord.Singletons

Methods

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

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

Defined in Data.Eq.Singletons

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

Defined in Data.Either.Singletons

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

Defined in Data.Either.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Eq.Singletons

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

Defined in Data.Functor.Identity.Singletons

SuppressUnusedWarnings (TFHelper_6989586621680109664Sym1 a6989586621680109669 :: TyFun (First a) Bool -> Type) 
Instance details

Defined in Data.Monoid.Singletons

SuppressUnusedWarnings (TFHelper_6989586621680109684Sym1 a6989586621680109689 :: TyFun (Last a) Bool -> Type) 
Instance details

Defined in Data.Monoid.Singletons

SuppressUnusedWarnings (TFHelper_6989586621679179231Sym1 a6989586621679179236 :: TyFun (Down a) Bool -> Type) 
Instance details

Defined in Data.Ord.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Proxy.Singletons

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

Defined in Data.Semigroup.Singletons

SuppressUnusedWarnings (TFHelper_6989586621679606240Sym1 a6989586621679606245 :: TyFun (First a) Bool -> Type) 
Instance details

Defined in Data.Semigroup.Singletons.Internal

SuppressUnusedWarnings (TFHelper_6989586621679606260Sym1 a6989586621679606265 :: TyFun (Last a) Bool -> Type) 
Instance details

Defined in Data.Semigroup.Singletons.Internal

SuppressUnusedWarnings (TFHelper_6989586621679606220Sym1 a6989586621679606225 :: TyFun (Max a) Bool -> Type) 
Instance details

Defined in Data.Semigroup.Singletons.Internal

SuppressUnusedWarnings (TFHelper_6989586621679606200Sym1 a6989586621679606205 :: TyFun (Min a) Bool -> Type) 
Instance details

Defined in Data.Semigroup.Singletons.Internal

SuppressUnusedWarnings (TFHelper_6989586621679606280Sym1 a6989586621679606285 :: TyFun (WrappedMonoid m) Bool -> Type) 
Instance details

Defined in Data.Semigroup.Singletons.Internal

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Semigroup.Singletons.Internal

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Semigroup.Singletons.Internal

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Semigroup.Singletons.Internal

SuppressUnusedWarnings (TFHelper_6989586621679130622Sym1 a6989586621679130627 :: TyFun (NonEmpty a) Bool -> Type) 
Instance details

Defined in Data.Eq.Singletons

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

Defined in Control.Monad.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.List.Singletons.Internal

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

Defined in Control.Monad.Singletons

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in GHC.Base.Singletons

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

Defined in Data.Eq.Singletons

SuppressUnusedWarnings (TFHelper_6989586621679130662Sym0 :: TyFun (a, b) ((a, b) ~> Bool) -> Type) 
Instance details

Defined in Data.Eq.Singletons

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

Defined in Data.Eq.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal.Disambiguation

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

Defined in Data.List.Singletons.Internal.Disambiguation

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

Defined in Data.Bool.Singletons

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Eq.Singletons

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

Defined in Data.Eq.Singletons

SuppressUnusedWarnings (TFHelper_6989586621679127817Sym1 a6989586621679127822 :: TyFun a Bool -> Type) 
Instance details

Defined in Data.Eq.Singletons

SuppressUnusedWarnings (TFHelper_6989586621679127828Sym1 a6989586621679127833 :: TyFun a Bool -> Type) 
Instance details

Defined in Data.Eq.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Ord.Singletons

SuppressUnusedWarnings (TFHelper_6989586621679166153Sym1 a6989586621679166158 :: TyFun a Bool -> Type) 
Instance details

Defined in Data.Ord.Singletons

SuppressUnusedWarnings (TFHelper_6989586621679166169Sym1 a6989586621679166174 :: TyFun a Bool -> Type) 
Instance details

Defined in Data.Ord.Singletons

SuppressUnusedWarnings (TFHelper_6989586621679166185Sym1 a6989586621679166190 :: TyFun a Bool -> Type) 
Instance details

Defined in Data.Ord.Singletons

SuppressUnusedWarnings (TFHelper_6989586621679166201Sym1 a6989586621679166206 :: TyFun a Bool -> Type) 
Instance details

Defined in Data.Ord.Singletons

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

Defined in Data.Eq.Singletons

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Bool.Singletons

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.List.Singletons.Internal

Methods

sing :: Sing (Elem_bySym2 d1 d2) #

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

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (AllSym1 d) #

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

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (AnySym1 d) #

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

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (ElemSym1 d) #

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

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (NotElemSym1 d) #

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

Defined in Data.Foldable.Singletons

Methods

sing :: Sing NullSym0 #

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

Defined in Data.Eq.Singletons

SuppressUnusedWarnings (TFHelper_6989586621680428549Sym0 :: TyFun (Const a b) (Const a b ~> Bool) -> Type) 
Instance details

Defined in Data.Functor.Const.Singletons

SuppressUnusedWarnings (TFHelper_6989586621680163384Sym1 a6989586621680163389 :: TyFun (Proxy s) Bool -> Type) 
Instance details

Defined in Data.Proxy.Singletons

SuppressUnusedWarnings (TFHelper_6989586621680605296Sym1 a6989586621680605301 :: TyFun (Arg a b) Bool -> Type) 
Instance details

Defined in Data.Semigroup.Singletons

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

Defined in Control.Monad.Singletons

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

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (TFHelper_6989586621679130662Sym1 a6989586621679130667 :: TyFun (a, b) Bool -> Type) 
Instance details

Defined in Data.Eq.Singletons

SuppressUnusedWarnings (TFHelper_6989586621679130700Sym0 :: TyFun (a, b, c) ((a, b, c) ~> Bool) -> Type) 
Instance details

Defined in Data.Eq.Singletons

SuppressUnusedWarnings (Bool_Sym2 a6989586621679120954 a6989586621679120955 :: TyFun Bool a -> Type) 
Instance details

Defined in Data.Bool.Singletons

SuppressUnusedWarnings (Elem_bySym2 a6989586621679731050 a6989586621679731051 :: TyFun [a] Bool -> Type) 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Let6989586621679731119Scrutinee_6989586621679727564Sym1 n6989586621679731117 :: TyFun k Bool -> Type) 
Instance details

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Control.Monad.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (TFHelper_6989586621680428549Sym1 a6989586621680428554 :: TyFun (Const a b) Bool -> Type) 
Instance details

Defined in Data.Functor.Const.Singletons

SuppressUnusedWarnings (TFHelper_6989586621679130700Sym1 a6989586621679130705 :: TyFun (a, b, c) Bool -> Type) 
Instance details

Defined in Data.Eq.Singletons

SuppressUnusedWarnings (TFHelper_6989586621679130749Sym0 :: TyFun (a, b, c, d) ((a, b, c, d) ~> Bool) -> Type) 
Instance details

Defined in Data.Eq.Singletons

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.Singletons.Base.Enum

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (Lambda_6989586621680193722Sym1 a_69895866216801937166989586621680193721 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (Let6989586621679731100Scrutinee_6989586621679727566Sym1 x6989586621679731097 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Let6989586621679731262Scrutinee_6989586621679727550Sym1 n6989586621679731259 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Let6989586621679731275Scrutinee_6989586621679727548Sym1 n6989586621679731272 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) 
Instance details

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Let6989586621679731363Scrutinee_6989586621679727542Sym2 x6989586621679731361 xs6989586621679731362 :: TyFun (k1 ~> Bool) (TyFun k Bool -> Type) -> Type) 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (TFHelper_6989586621679130749Sym1 a6989586621679130754 :: TyFun (a, b, c, d) Bool -> Type) 
Instance details

Defined in Data.Eq.Singletons

SuppressUnusedWarnings (TFHelper_6989586621679130809Sym0 :: TyFun (a, b, c, d, e) ((a, b, c, d, e) ~> Bool) -> Type) 
Instance details

Defined in Data.Eq.Singletons

SuppressUnusedWarnings (Let6989586621679731071Scrutinee_6989586621679727570Sym2 y6989586621679731068 ys6989586621679731069 :: TyFun [k1] (TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type) -> Type) 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Let6989586621679731087Scrutinee_6989586621679727568Sym2 x6989586621679731084 xs6989586621679731085 :: TyFun [k1] (TyFun k3 Bool -> Type) -> Type) 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Let6989586621679516356Scrutinee_6989586621679516279Sym0 :: 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.Base.Enum

SuppressUnusedWarnings (Let6989586621679516393Scrutinee_6989586621679516269Sym0 :: 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.Base.Enum

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

Defined in Data.Singletons.Base.Enum

SuppressUnusedWarnings (Let6989586621679731185Scrutinee_6989586621679727560Sym2 key6989586621679731181 x6989586621679731182 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Lambda_6989586621680892729Sym2 x6989586621680892728 p6989586621680892724 :: TyFun k3 (TyFun Bool ([k1] ~> [k1]) -> Type) -> Type) 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (Lambda_6989586621680193722Sym2 a_69895866216801937166989586621680193721 arg_69895866216801931086989586621680193724 :: TyFun k3 Bool -> Type) 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (Let6989586621679731100Scrutinee_6989586621679727566Sym2 x6989586621679731097 xs6989586621679731098 :: TyFun k3 Bool -> Type) 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Let6989586621679731262Scrutinee_6989586621679727550Sym2 n6989586621679731259 x6989586621679731260 :: TyFun k3 Bool -> Type) 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Let6989586621679731275Scrutinee_6989586621679727548Sym2 n6989586621679731272 x6989586621679731273 :: TyFun k3 Bool -> Type) 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Let6989586621679731071Scrutinee_6989586621679727570Sym3 y6989586621679731068 ys6989586621679731069 xs6989586621679731070 :: TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type) 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (TFHelper_6989586621679130809Sym1 a6989586621679130814 :: TyFun (a, b, c, d, e) Bool -> Type) 
Instance details

Defined in Data.Eq.Singletons

SuppressUnusedWarnings (TFHelper_6989586621679130880Sym0 :: TyFun (a, b, c, d, e, f) ((a, b, c, d, e, f) ~> Bool) -> Type) 
Instance details

Defined in Data.Eq.Singletons

SuppressUnusedWarnings (Lambda_6989586621680892729Sym3 x6989586621680892728 p6989586621680892724 a_69895866216808927176989586621680892725 :: TyFun Bool ([k1] ~> [k1]) -> Type) 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (Let6989586621679731363Scrutinee_6989586621679727542Sym3 x6989586621679731361 xs6989586621679731362 p6989586621679731357 :: TyFun k Bool -> Type) 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Let6989586621679516447Scrutinee_6989586621679516255Sym2 x6989586621679516446 x06989586621679516441 :: TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Base.Enum

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

Defined in Data.Singletons.Base.Enum

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

Defined in Data.Singletons.Base.Enum

SuppressUnusedWarnings (Let6989586621679731087Scrutinee_6989586621679727568Sym3 x6989586621679731084 xs6989586621679731085 ls6989586621679731086 :: TyFun k3 Bool -> Type) 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Let6989586621679731185Scrutinee_6989586621679727560Sym3 key6989586621679731181 x6989586621679731182 y6989586621679731183 :: TyFun k3 Bool -> Type) 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (TFHelper_6989586621679130880Sym1 a6989586621679130885 :: TyFun (a, b, c, d, e, f) Bool -> Type) 
Instance details

Defined in Data.Eq.Singletons

SuppressUnusedWarnings (TFHelper_6989586621679130962Sym0 :: TyFun (a, b, c, d, e, f, g) ((a, b, c, d, e, f, g) ~> Bool) -> Type) 
Instance details

Defined in Data.Eq.Singletons

SuppressUnusedWarnings (Let6989586621679516356Scrutinee_6989586621679516279Sym2 x16989586621679516351 x26989586621679516352 :: TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Base.Enum

SuppressUnusedWarnings (Let6989586621679516393Scrutinee_6989586621679516269Sym2 x16989586621679516388 x26989586621679516389 :: TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Base.Enum

SuppressUnusedWarnings (Let6989586621679516447Scrutinee_6989586621679516255Sym3 x6989586621679516446 x06989586621679516441 y6989586621679516442 :: TyFun k3 (TyFun k4 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Base.Enum

SuppressUnusedWarnings (Let6989586621679731071Scrutinee_6989586621679727570Sym4 y6989586621679731068 ys6989586621679731069 xs6989586621679731070 eq6989586621679731062 :: TyFun k3 Bool -> Type) 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (TFHelper_6989586621679130962Sym1 a6989586621679130967 :: TyFun (a, b, c, d, e, f, g) Bool -> Type) 
Instance details

Defined in Data.Eq.Singletons

SuppressUnusedWarnings (Let6989586621679516356Scrutinee_6989586621679516279Sym3 x16989586621679516351 x26989586621679516352 y6989586621679516353 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Base.Enum

SuppressUnusedWarnings (Let6989586621679516393Scrutinee_6989586621679516269Sym3 x16989586621679516388 x26989586621679516389 y6989586621679516390 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Base.Enum

SuppressUnusedWarnings (Let6989586621679516447Scrutinee_6989586621679516255Sym4 x6989586621679516446 x06989586621679516441 y6989586621679516442 arg_69895866216795162516989586621679516437 :: TyFun k4 Bool -> Type) 
Instance details

Defined in Data.Singletons.Base.Enum

SuppressUnusedWarnings (Let6989586621679516356Scrutinee_6989586621679516279Sym4 x16989586621679516351 x26989586621679516352 y6989586621679516353 arg_69895866216795162736989586621679516346 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Base.Enum

SuppressUnusedWarnings (Let6989586621679516393Scrutinee_6989586621679516269Sym4 x16989586621679516388 x26989586621679516389 y6989586621679516390 arg_69895866216795162636989586621679516383 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type) 
Instance details

Defined in Data.Singletons.Base.Enum

SuppressUnusedWarnings (Let6989586621679516356Scrutinee_6989586621679516279Sym5 x16989586621679516351 x26989586621679516352 y6989586621679516353 arg_69895866216795162736989586621679516346 arg_69895866216795162756989586621679516347 :: TyFun k5 Bool -> Type) 
Instance details

Defined in Data.Singletons.Base.Enum

SuppressUnusedWarnings (Let6989586621679516393Scrutinee_6989586621679516269Sym5 x16989586621679516388 x26989586621679516389 y6989586621679516390 arg_69895866216795162636989586621679516383 arg_69895866216795162656989586621679516384 :: TyFun k5 Bool -> Type) 
Instance details

Defined in Data.Singletons.Base.Enum

type DemoteRep Bool 
Instance details

Defined in GHC.Generics

type DemoteRep Bool = Bool
type Rep Bool

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

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

Defined in GHC.Generics

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

Defined in Morley.AsRPC

type AsRPC Bool = Bool
type TypeDocFieldDescriptions Bool 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

type ToT Bool 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

type ToT Bool = 'TBool
type Demote Bool 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = SBool
type MaxBound 
Instance details

Defined in Data.Singletons.Base.Enum

type MaxBound = MaxBound_6989586621679509887Sym0
type MinBound 
Instance details

Defined in Data.Singletons.Base.Enum

type MinBound = MinBound_6989586621679509884Sym0
newtype Vector Bool 
Instance details

Defined in Data.Vector.Unboxed.Base

type UnaryArithResHs Not Bool Source # 
Instance details

Defined in Lorentz.Arith

type FromEnum (a :: Bool) 
Instance details

Defined in Data.Singletons.Base.Enum

type FromEnum (a :: Bool) = Apply FromEnum_6989586621679544301Sym0 a
type Pred (arg :: Bool) 
Instance details

Defined in Data.Singletons.Base.Enum

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

Defined in Data.Singletons.Base.Enum

type Succ (arg :: Bool) = Apply (Succ_6989586621679516481Sym0 :: TyFun Bool Bool -> Type) arg
type ToEnum a 
Instance details

Defined in Data.Singletons.Base.Enum

type ToEnum a = Apply ToEnum_6989586621679544288Sym0 a
type Show_ (arg :: Bool) 
Instance details

Defined in Text.Show.Singletons

type Show_ (arg :: Bool) = Apply (Show__6989586621680047550Sym0 :: TyFun Bool Symbol -> Type) arg
newtype MVector s Bool 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Bool = MV_Bool (MVector s Word8)
type (arg1 :: Bool) /= (arg2 :: Bool) 
Instance details

Defined in Data.Eq.Singletons

type (arg1 :: Bool) /= (arg2 :: Bool) = Apply (Apply (TFHelper_6989586621679127817Sym0 :: TyFun Bool (Bool ~> Bool) -> Type) arg1) arg2
type (a1 :: Bool) == (a2 :: Bool) 
Instance details

Defined in Data.Eq.Singletons

type (a1 :: Bool) == (a2 :: Bool) = Apply (Apply TFHelper_6989586621679131019Sym0 a1) a2
type (arg1 :: Bool) < (arg2 :: Bool) 
Instance details

Defined in Data.Ord.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Ord.Singletons

type Compare (a1 :: Bool) (a2 :: Bool) = Apply (Apply Compare_6989586621679181840Sym0 a1) a2
type Max (arg1 :: Bool) (arg2 :: Bool) 
Instance details

Defined in Data.Ord.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Singletons.Base.Enum

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

Defined in Text.Show.Singletons

type ShowList (arg1 :: [Bool]) arg2 = Apply (Apply (ShowList_6989586621680047558Sym0 :: TyFun [Bool] (Symbol ~> Symbol) -> Type) arg1) arg2
type Apply GetAllSym0 (a6989586621679596382 :: All) 
Instance details

Defined in Data.Semigroup.Singletons.Internal

type Apply GetAllSym0 (a6989586621679596382 :: All) = GetAll a6989586621679596382
type Apply GetAnySym0 (a6989586621679596398 :: Any) 
Instance details

Defined in Data.Semigroup.Singletons.Internal

type Apply GetAnySym0 (a6989586621679596398 :: Any) = GetAny a6989586621679596398
type Apply ContainsBigMapSym (x :: T) 
Instance details

Defined in Morley.Michelson.Typed.Scope

type Apply ContainsBigMapSym (x :: T) = ContainsBigMap x
type Apply ContainsContractSym (x :: T) 
Instance details

Defined in Morley.Michelson.Typed.Scope

type Apply ContainsContractSym (x :: T) = ContainsContract x
type Apply ContainsNestedBigMapsSym (x :: T) 
Instance details

Defined in Morley.Michelson.Typed.Scope

type Apply ContainsNestedBigMapsSym (x :: T) = ContainsNestedBigMaps x
type Apply ContainsOpSym (x :: T) 
Instance details

Defined in Morley.Michelson.Typed.Scope

type Apply ContainsOpSym (x :: T) = ContainsOp x
type Apply ContainsTicketSym (x :: T) 
Instance details

Defined in Morley.Michelson.Typed.Scope

type Apply ContainsTicketSym (x :: T) = ContainsTicket x
type Apply AllSym0 (a6989586621679596379 :: Bool) 
Instance details

Defined in Data.Semigroup.Singletons.Internal

type Apply AllSym0 (a6989586621679596379 :: Bool) = 'All a6989586621679596379
type Apply All_Sym0 (a6989586621679713097 :: Bool) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Disambiguation

type Apply All_Sym0 (a6989586621679713097 :: Bool) = All_ a6989586621679713097
type Apply AnySym0 (a6989586621679596395 :: Bool) 
Instance details

Defined in Data.Semigroup.Singletons.Internal

type Apply AnySym0 (a6989586621679596395 :: Bool) = 'Any a6989586621679596395
type Apply Any_Sym0 (a6989586621679713091 :: Bool) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Disambiguation

type Apply Any_Sym0 (a6989586621679713091 :: Bool) = Any_ a6989586621679713091
type Apply NotSym0 (a6989586621679123820 :: Bool) 
Instance details

Defined in Data.Bool.Singletons

type Apply NotSym0 (a6989586621679123820 :: Bool) = Not a6989586621679123820
type Apply FromEnum_6989586621679544301Sym0 (a6989586621679544305 :: Bool) 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply FromEnum_6989586621679544301Sym0 (a6989586621679544305 :: Bool) = FromEnum_6989586621679544301 a6989586621679544305
type Apply ToEnum_6989586621679544288Sym0 (a6989586621679544292 :: Nat) 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply ToEnum_6989586621679544288Sym0 (a6989586621679544292 :: Nat) = ToEnum_6989586621679544288 a6989586621679544292
type EnumFromThenTo (arg1 :: Bool) (arg2 :: Bool) (arg3 :: Bool) 
Instance details

Defined in Data.Singletons.Base.Enum

type EnumFromThenTo (arg1 :: Bool) (arg2 :: Bool) (arg3 :: Bool) = Apply (Apply (Apply (EnumFromThenTo_6989586621679516516Sym0 :: TyFun Bool (Bool ~> (Bool ~> [Bool])) -> Type) arg1) arg2) arg3
type ShowsPrec a1 (a2 :: Bool) a3 
Instance details

Defined in Text.Show.Singletons

type ShowsPrec a1 (a2 :: Bool) a3 = Apply (Apply (Apply ShowsPrec_6989586621680071834Sym0 a1) a2) a3
type Apply (TFHelper_6989586621679606123Sym1 a6989586621679606128 :: TyFun All Bool -> Type) (a6989586621679606129 :: All) 
Instance details

Defined in Data.Semigroup.Singletons.Internal

type Apply (TFHelper_6989586621679606123Sym1 a6989586621679606128 :: TyFun All Bool -> Type) (a6989586621679606129 :: All) = TFHelper_6989586621679606123 a6989586621679606128 a6989586621679606129
type Apply (TFHelper_6989586621679606140Sym1 a6989586621679606145 :: TyFun Any Bool -> Type) (a6989586621679606146 :: Any) 
Instance details

Defined in Data.Semigroup.Singletons.Internal

type Apply (TFHelper_6989586621679606140Sym1 a6989586621679606145 :: TyFun Any Bool -> Type) (a6989586621679606146 :: Any) = TFHelper_6989586621679606140 a6989586621679606145 a6989586621679606146
type Apply (TFHelper_6989586621679130639Sym1 a6989586621679130644 :: TyFun Void Bool -> Type) (a6989586621679130645 :: Void) 
Instance details

Defined in Data.Eq.Singletons

type Apply (TFHelper_6989586621679130639Sym1 a6989586621679130644 :: TyFun Void Bool -> Type) (a6989586621679130645 :: Void) = TFHelper_6989586621679130639 a6989586621679130644 a6989586621679130645
type Apply (TFHelper_6989586621679131028Sym1 a6989586621679131033 :: TyFun Ordering Bool -> Type) (a6989586621679131034 :: Ordering) 
Instance details

Defined in Data.Eq.Singletons

type Apply (TFHelper_6989586621679131028Sym1 a6989586621679131033 :: TyFun Ordering Bool -> Type) (a6989586621679131034 :: Ordering) = TFHelper_6989586621679131028 a6989586621679131033 a6989586621679131034
type Apply (TFHelper_6989586621679131037Sym1 a6989586621679131042 :: TyFun () Bool -> Type) (a6989586621679131043 :: ()) 
Instance details

Defined in Data.Eq.Singletons

type Apply (TFHelper_6989586621679131037Sym1 a6989586621679131042 :: TyFun () Bool -> Type) (a6989586621679131043 :: ()) = TFHelper_6989586621679131037 a6989586621679131042 a6989586621679131043
type Apply (Compare_6989586621679181840Sym1 a6989586621679181845 :: TyFun Bool Ordering -> Type) (a6989586621679181846 :: Bool) 
Instance details

Defined in Data.Ord.Singletons

type Apply (Compare_6989586621679181840Sym1 a6989586621679181845 :: TyFun Bool Ordering -> Type) (a6989586621679181846 :: Bool) = Compare_6989586621679181840 a6989586621679181845 a6989586621679181846
type Apply ((&&@#@$$) a6989586621679122836 :: TyFun Bool Bool -> Type) (a6989586621679122837 :: Bool) 
Instance details

Defined in Data.Bool.Singletons

type Apply ((&&@#@$$) a6989586621679122836 :: TyFun Bool Bool -> Type) (a6989586621679122837 :: Bool) = a6989586621679122836 && a6989586621679122837
type Apply ((||@#@$$) a6989586621679123482 :: TyFun Bool Bool -> Type) (a6989586621679123483 :: Bool) 
Instance details

Defined in Data.Bool.Singletons

type Apply ((||@#@$$) a6989586621679123482 :: TyFun Bool Bool -> Type) (a6989586621679123483 :: Bool) = a6989586621679123482 || a6989586621679123483
type Apply (TFHelper_6989586621679131019Sym1 a6989586621679131024 :: TyFun Bool Bool -> Type) (a6989586621679131025 :: Bool) 
Instance details

Defined in Data.Eq.Singletons

type Apply (TFHelper_6989586621679131019Sym1 a6989586621679131024 :: TyFun Bool Bool -> Type) (a6989586621679131025 :: Bool) = TFHelper_6989586621679131019 a6989586621679131024 a6989586621679131025
type Apply ((<=?@#@$$) a6989586621679462422 :: TyFun Nat Bool -> Type) (a6989586621679462423 :: Nat) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Apply ((<=?@#@$$) a6989586621679462422 :: TyFun Nat Bool -> Type) (a6989586621679462423 :: Nat) = a6989586621679462422 <=? a6989586621679462423
type Apply (Let6989586621680163560Scrutinee_6989586621680162757Sym0 :: TyFun k1 Bool -> Type) (n6989586621680163559 :: k1) 
Instance details

Defined in Data.Proxy.Singletons

type Apply (Let6989586621680163560Scrutinee_6989586621680162757Sym0 :: TyFun k1 Bool -> Type) (n6989586621680163559 :: k1) = Let6989586621680163560Scrutinee_6989586621680162757 n6989586621680163559
type Apply ((/=@#@$$) a6989586621679127813 :: TyFun a Bool -> Type) (a6989586621679127814 :: a) 
Instance details

Defined in Data.Eq.Singletons

type Apply ((/=@#@$$) a6989586621679127813 :: TyFun a Bool -> Type) (a6989586621679127814 :: a) = a6989586621679127813 /= a6989586621679127814
type Apply ((==@#@$$) a6989586621679127808 :: TyFun a Bool -> Type) (a6989586621679127809 :: a) 
Instance details

Defined in Data.Eq.Singletons

type Apply ((==@#@$$) a6989586621679127808 :: TyFun a Bool -> Type) (a6989586621679127809 :: a) = a6989586621679127808 == a6989586621679127809
type Apply (TFHelper_6989586621679127817Sym1 a6989586621679127822 :: TyFun a Bool -> Type) (a6989586621679127823 :: a) 
Instance details

Defined in Data.Eq.Singletons

type Apply (TFHelper_6989586621679127817Sym1 a6989586621679127822 :: TyFun a Bool -> Type) (a6989586621679127823 :: a) = TFHelper_6989586621679127817 a6989586621679127822 a6989586621679127823
type Apply (TFHelper_6989586621679127828Sym1 a6989586621679127833 :: TyFun a Bool -> Type) (a6989586621679127834 :: a) 
Instance details

Defined in Data.Eq.Singletons

type Apply (TFHelper_6989586621679127828Sym1 a6989586621679127833 :: TyFun a Bool -> Type) (a6989586621679127834 :: a) = TFHelper_6989586621679127828 a6989586621679127833 a6989586621679127834
type Apply ((<=@#@$$) a6989586621679166108 :: TyFun a Bool -> Type) (a6989586621679166109 :: a) 
Instance details

Defined in Data.Ord.Singletons

type Apply ((<=@#@$$) a6989586621679166108 :: TyFun a Bool -> Type) (a6989586621679166109 :: a) = a6989586621679166108 <= a6989586621679166109
type Apply ((<@#@$$) a6989586621679166103 :: TyFun a Bool -> Type) (a6989586621679166104 :: a) 
Instance details

Defined in Data.Ord.Singletons

type Apply ((<@#@$$) a6989586621679166103 :: TyFun a Bool -> Type) (a6989586621679166104 :: a) = a6989586621679166103 < a6989586621679166104
type Apply ((>=@#@$$) a6989586621679166118 :: TyFun a Bool -> Type) (a6989586621679166119 :: a) 
Instance details

Defined in Data.Ord.Singletons

type Apply ((>=@#@$$) a6989586621679166118 :: TyFun a Bool -> Type) (a6989586621679166119 :: a) = a6989586621679166118 >= a6989586621679166119
type Apply ((>@#@$$) a6989586621679166113 :: TyFun a Bool -> Type) (a6989586621679166114 :: a) 
Instance details

Defined in Data.Ord.Singletons

type Apply ((>@#@$$) a6989586621679166113 :: TyFun a Bool -> Type) (a6989586621679166114 :: a) = a6989586621679166113 > a6989586621679166114
type Apply (TFHelper_6989586621679166153Sym1 a6989586621679166158 :: TyFun a Bool -> Type) (a6989586621679166159 :: a) 
Instance details

Defined in Data.Ord.Singletons

type Apply (TFHelper_6989586621679166153Sym1 a6989586621679166158 :: TyFun a Bool -> Type) (a6989586621679166159 :: a) = TFHelper_6989586621679166153 a6989586621679166158 a6989586621679166159
type Apply (TFHelper_6989586621679166169Sym1 a6989586621679166174 :: TyFun a Bool -> Type) (a6989586621679166175 :: a) 
Instance details

Defined in Data.Ord.Singletons

type Apply (TFHelper_6989586621679166169Sym1 a6989586621679166174 :: TyFun a Bool -> Type) (a6989586621679166175 :: a) = TFHelper_6989586621679166169 a6989586621679166174 a6989586621679166175
type Apply (TFHelper_6989586621679166185Sym1 a6989586621679166190 :: TyFun a Bool -> Type) (a6989586621679166191 :: a) 
Instance details

Defined in Data.Ord.Singletons

type Apply (TFHelper_6989586621679166185Sym1 a6989586621679166190 :: TyFun a Bool -> Type) (a6989586621679166191 :: a) = TFHelper_6989586621679166185 a6989586621679166190 a6989586621679166191
type Apply (TFHelper_6989586621679166201Sym1 a6989586621679166206 :: TyFun a Bool -> Type) (a6989586621679166207 :: a) 
Instance details

Defined in Data.Ord.Singletons

type Apply (TFHelper_6989586621679166201Sym1 a6989586621679166206 :: TyFun a Bool -> Type) (a6989586621679166207 :: a) = TFHelper_6989586621679166201 a6989586621679166206 a6989586621679166207
type Apply (DefaultEqSym1 a6989586621679130155 :: TyFun k Bool -> Type) (a6989586621679130156 :: k) 
Instance details

Defined in Data.Eq.Singletons

type Apply (DefaultEqSym1 a6989586621679130155 :: TyFun k Bool -> Type) (a6989586621679130156 :: k) = DefaultEq a6989586621679130155 a6989586621679130156
type Apply (Let6989586621680184051Scrutinee_6989586621680184015Sym1 x6989586621680184046 :: TyFun k1 Bool -> Type) (y6989586621680184047 :: k1) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Let6989586621680184051Scrutinee_6989586621680184015Sym1 x6989586621680184046 :: TyFun k1 Bool -> Type) (y6989586621680184047 :: k1) = Let6989586621680184051Scrutinee_6989586621680184015 x6989586621680184046 y6989586621680184047
type Apply (Let6989586621680184075Scrutinee_6989586621680184017Sym1 x6989586621680184070 :: TyFun k1 Bool -> Type) (y6989586621680184071 :: k1) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Let6989586621680184075Scrutinee_6989586621680184017Sym1 x6989586621680184070 :: TyFun k1 Bool -> Type) (y6989586621680184071 :: k1) = Let6989586621680184075Scrutinee_6989586621680184017 x6989586621680184070 y6989586621680184071
type Apply (Let6989586621679166141Scrutinee_6989586621679163721Sym1 x6989586621679166139 :: TyFun k1 Bool -> Type) (y6989586621679166140 :: k1) 
Instance details

Defined in Data.Ord.Singletons

type Apply (Let6989586621679166141Scrutinee_6989586621679163721Sym1 x6989586621679166139 :: TyFun k1 Bool -> Type) (y6989586621679166140 :: k1) = Let6989586621679166141Scrutinee_6989586621679163721 x6989586621679166139 y6989586621679166140
type Apply (Let6989586621679166145Scrutinee_6989586621679163723Sym1 x6989586621679166139 :: TyFun k1 Bool -> Type) (y6989586621679166140 :: k1) 
Instance details

Defined in Data.Ord.Singletons

type Apply (Let6989586621679166145Scrutinee_6989586621679163723Sym1 x6989586621679166139 :: TyFun k1 Bool -> Type) (y6989586621679166140 :: k1) = Let6989586621679166145Scrutinee_6989586621679163723 x6989586621679166139 y6989586621679166140
type Apply (Let6989586621679166226Scrutinee_6989586621679163733Sym1 x6989586621679166224 :: TyFun k1 Bool -> Type) (y6989586621679166225 :: k1) 
Instance details

Defined in Data.Ord.Singletons

type Apply (Let6989586621679166226Scrutinee_6989586621679163733Sym1 x6989586621679166224 :: TyFun k1 Bool -> Type) (y6989586621679166225 :: k1) = Let6989586621679166226Scrutinee_6989586621679163733 x6989586621679166224 y6989586621679166225
type Apply (Let6989586621679166242Scrutinee_6989586621679163735Sym1 x6989586621679166240 :: TyFun k1 Bool -> Type) (y6989586621679166241 :: k1) 
Instance details

Defined in Data.Ord.Singletons

type Apply (Let6989586621679166242Scrutinee_6989586621679163735Sym1 x6989586621679166240 :: TyFun k1 Bool -> Type) (y6989586621679166241 :: k1) = Let6989586621679166242Scrutinee_6989586621679163735 x6989586621679166240 y6989586621679166241
type Apply (Bool_Sym2 a6989586621679120954 a6989586621679120955 :: TyFun Bool a -> Type) (a6989586621679120956 :: Bool) 
Instance details

Defined in Data.Bool.Singletons

type Apply (Bool_Sym2 a6989586621679120954 a6989586621679120955 :: TyFun Bool a -> Type) (a6989586621679120956 :: Bool) = Bool_ a6989586621679120954 a6989586621679120955 a6989586621679120956
type Apply (Let6989586621679731119Scrutinee_6989586621679727564Sym1 n6989586621679731117 :: TyFun k Bool -> Type) (x6989586621679731118 :: k) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Let6989586621679731119Scrutinee_6989586621679727564Sym1 n6989586621679731117 :: TyFun k Bool -> Type) (x6989586621679731118 :: k) = Let6989586621679731119Scrutinee_6989586621679727564 n6989586621679731117 x6989586621679731118
type Apply (Lambda_6989586621680193722Sym2 a_69895866216801937166989586621680193721 arg_69895866216801931086989586621680193724 :: TyFun k3 Bool -> Type) (arg_69895866216801931106989586621680193725 :: k3) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Lambda_6989586621680193722Sym2 a_69895866216801937166989586621680193721 arg_69895866216801931086989586621680193724 :: TyFun k3 Bool -> Type) (arg_69895866216801931106989586621680193725 :: k3) = Lambda_6989586621680193722 a_69895866216801937166989586621680193721 arg_69895866216801931086989586621680193724 arg_69895866216801931106989586621680193725
type Apply (Let6989586621679731100Scrutinee_6989586621679727566Sym2 x6989586621679731097 xs6989586621679731098 :: TyFun k3 Bool -> Type) (n6989586621679731099 :: k3) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Let6989586621679731100Scrutinee_6989586621679727566Sym2 x6989586621679731097 xs6989586621679731098 :: TyFun k3 Bool -> Type) (n6989586621679731099 :: k3) = Let6989586621679731100Scrutinee_6989586621679727566 x6989586621679731097 xs6989586621679731098 n6989586621679731099
type Apply (Let6989586621679731262Scrutinee_6989586621679727550Sym2 n6989586621679731259 x6989586621679731260 :: TyFun k3 Bool -> Type) (xs6989586621679731261 :: k3) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Let6989586621679731262Scrutinee_6989586621679727550Sym2 n6989586621679731259 x6989586621679731260 :: TyFun k3 Bool -> Type) (xs6989586621679731261 :: k3) = Let6989586621679731262Scrutinee_6989586621679727550 n6989586621679731259 x6989586621679731260 xs6989586621679731261
type Apply (Let6989586621679731275Scrutinee_6989586621679727548Sym2 n6989586621679731272 x6989586621679731273 :: TyFun k3 Bool -> Type) (xs6989586621679731274 :: k3) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Let6989586621679731275Scrutinee_6989586621679727548Sym2 n6989586621679731272 x6989586621679731273 :: TyFun k3 Bool -> Type) (xs6989586621679731274 :: k3) = Let6989586621679731275Scrutinee_6989586621679727548 n6989586621679731272 x6989586621679731273 xs6989586621679731274
type Apply (Let6989586621679731363Scrutinee_6989586621679727542Sym3 x6989586621679731361 xs6989586621679731362 p6989586621679731357 :: TyFun k Bool -> Type) (a_69895866216797313506989586621679731358 :: k) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Let6989586621679731363Scrutinee_6989586621679727542Sym3 x6989586621679731361 xs6989586621679731362 p6989586621679731357 :: TyFun k Bool -> Type) (a_69895866216797313506989586621679731358 :: k) = Let6989586621679731363Scrutinee_6989586621679727542 x6989586621679731361 xs6989586621679731362 p6989586621679731357 a_69895866216797313506989586621679731358
type Apply (Let6989586621679731087Scrutinee_6989586621679727568Sym3 x6989586621679731084 xs6989586621679731085 ls6989586621679731086 :: TyFun k3 Bool -> Type) (l6989586621679731079 :: k3) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Let6989586621679731087Scrutinee_6989586621679727568Sym3 x6989586621679731084 xs6989586621679731085 ls6989586621679731086 :: TyFun k3 Bool -> Type) (l6989586621679731079 :: k3) = Let6989586621679731087Scrutinee_6989586621679727568 x6989586621679731084 xs6989586621679731085 ls6989586621679731086 l6989586621679731079
type Apply (Let6989586621679731185Scrutinee_6989586621679727560Sym3 key6989586621679731181 x6989586621679731182 y6989586621679731183 :: TyFun k3 Bool -> Type) (xys6989586621679731184 :: k3) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Let6989586621679731185Scrutinee_6989586621679727560Sym3 key6989586621679731181 x6989586621679731182 y6989586621679731183 :: TyFun k3 Bool -> Type) (xys6989586621679731184 :: k3) = Let6989586621679731185Scrutinee_6989586621679727560 key6989586621679731181 x6989586621679731182 y6989586621679731183 xys6989586621679731184
type Apply (Let6989586621679731071Scrutinee_6989586621679727570Sym4 y6989586621679731068 ys6989586621679731069 xs6989586621679731070 eq6989586621679731062 :: TyFun k3 Bool -> Type) (l6989586621679731063 :: k3) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Let6989586621679731071Scrutinee_6989586621679727570Sym4 y6989586621679731068 ys6989586621679731069 xs6989586621679731070 eq6989586621679731062 :: TyFun k3 Bool -> Type) (l6989586621679731063 :: k3) = Let6989586621679731071Scrutinee_6989586621679727570 y6989586621679731068 ys6989586621679731069 xs6989586621679731070 eq6989586621679731062 l6989586621679731063
type Apply (Let6989586621679516447Scrutinee_6989586621679516255Sym4 x6989586621679516446 x06989586621679516441 y6989586621679516442 arg_69895866216795162516989586621679516437 :: TyFun k4 Bool -> Type) (arg_69895866216795162536989586621679516438 :: k4) 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (Let6989586621679516447Scrutinee_6989586621679516255Sym4 x6989586621679516446 x06989586621679516441 y6989586621679516442 arg_69895866216795162516989586621679516437 :: TyFun k4 Bool -> Type) (arg_69895866216795162536989586621679516438 :: k4) = Let6989586621679516447Scrutinee_6989586621679516255 x6989586621679516446 x06989586621679516441 y6989586621679516442 arg_69895866216795162516989586621679516437 arg_69895866216795162536989586621679516438
type Apply (Let6989586621679516356Scrutinee_6989586621679516279Sym5 x16989586621679516351 x26989586621679516352 y6989586621679516353 arg_69895866216795162736989586621679516346 arg_69895866216795162756989586621679516347 :: TyFun k5 Bool -> Type) (arg_69895866216795162776989586621679516348 :: k5) 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (Let6989586621679516356Scrutinee_6989586621679516279Sym5 x16989586621679516351 x26989586621679516352 y6989586621679516353 arg_69895866216795162736989586621679516346 arg_69895866216795162756989586621679516347 :: TyFun k5 Bool -> Type) (arg_69895866216795162776989586621679516348 :: k5) = Let6989586621679516356Scrutinee_6989586621679516279 x16989586621679516351 x26989586621679516352 y6989586621679516353 arg_69895866216795162736989586621679516346 arg_69895866216795162756989586621679516347 arg_69895866216795162776989586621679516348
type Apply (Let6989586621679516393Scrutinee_6989586621679516269Sym5 x16989586621679516388 x26989586621679516389 y6989586621679516390 arg_69895866216795162636989586621679516383 arg_69895866216795162656989586621679516384 :: TyFun k5 Bool -> Type) (arg_69895866216795162676989586621679516385 :: k5) 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (Let6989586621679516393Scrutinee_6989586621679516269Sym5 x16989586621679516388 x26989586621679516389 y6989586621679516390 arg_69895866216795162636989586621679516383 arg_69895866216795162656989586621679516384 :: TyFun k5 Bool -> Type) (arg_69895866216795162676989586621679516385 :: k5) = Let6989586621679516393Scrutinee_6989586621679516269 x16989586621679516388 x26989586621679516389 y6989586621679516390 arg_69895866216795162636989586621679516383 arg_69895866216795162656989586621679516384 arg_69895866216795162676989586621679516385
type Eval (Not 'False) 
Instance details

Defined in Fcf.Data.Bool

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

Defined in Fcf.Data.Bool

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

Defined in Control.Monad.Singletons.Internal

type Apply (GuardSym0 :: TyFun Bool (f ()) -> Type) (a6989586621679286827 :: Bool) = Guard a6989586621679286827 :: f ()
type Eval (And lst :: Bool -> Type) 
Instance details

Defined in Fcf.Class.Foldable

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

Defined in Fcf.Class.Foldable

type Eval (Or lst :: Bool -> Type) = Eval (Foldr (||) 'False lst)
type Eval ('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 && 'False :: Bool -> Type) 
Instance details

Defined in Fcf.Data.Bool

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

Defined in Fcf.Data.Bool

type Eval (a && 'True :: Bool -> Type) = a
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 (IsJust ('Just _a) :: Bool -> Type) 
Instance details

Defined in Fcf.Data.Common

type Eval (IsJust ('Just _a) :: Bool -> Type) = 'True
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 (IsNothing ('Just _a) :: Bool -> Type) 
Instance details

Defined in Fcf.Data.Common

type Eval (IsNothing ('Just _a) :: 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 (Null ('[] :: [a]) :: Bool -> Type) 
Instance details

Defined in Fcf.Data.List

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

Defined in Fcf.Data.List

type Eval (Null (a2 ': as) :: Bool -> Type) = 'False
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) = 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 (a >= b :: Bool -> Type) 
Instance details

Defined in Fcf.Data.Nat

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

Defined in Data.Semigroup.Singletons.Internal

type Apply TFHelper_6989586621679606123Sym0 (a6989586621679606128 :: All) = TFHelper_6989586621679606123Sym1 a6989586621679606128
type Apply TFHelper_6989586621679606140Sym0 (a6989586621679606145 :: Any) 
Instance details

Defined in Data.Semigroup.Singletons.Internal

type Apply TFHelper_6989586621679606140Sym0 (a6989586621679606145 :: Any) = TFHelper_6989586621679606140Sym1 a6989586621679606145
type Apply TFHelper_6989586621679130639Sym0 (a6989586621679130644 :: Void) 
Instance details

Defined in Data.Eq.Singletons

type Apply TFHelper_6989586621679130639Sym0 (a6989586621679130644 :: Void) = TFHelper_6989586621679130639Sym1 a6989586621679130644
type Apply TFHelper_6989586621679131028Sym0 (a6989586621679131033 :: Ordering) 
Instance details

Defined in Data.Eq.Singletons

type Apply TFHelper_6989586621679131028Sym0 (a6989586621679131033 :: Ordering) = TFHelper_6989586621679131028Sym1 a6989586621679131033
type Apply TFHelper_6989586621679131037Sym0 (a6989586621679131042 :: ()) 
Instance details

Defined in Data.Eq.Singletons

type Apply TFHelper_6989586621679131037Sym0 (a6989586621679131042 :: ()) = TFHelper_6989586621679131037Sym1 a6989586621679131042
type Apply ShowParenSym0 (a6989586621680047463 :: Bool) 
Instance details

Defined in Text.Show.Singletons

type Apply ShowParenSym0 (a6989586621680047463 :: Bool) = ShowParenSym1 a6989586621680047463
type Apply Compare_6989586621679181840Sym0 (a6989586621679181845 :: Bool) 
Instance details

Defined in Data.Ord.Singletons

type Apply Compare_6989586621679181840Sym0 (a6989586621679181845 :: Bool) = Compare_6989586621679181840Sym1 a6989586621679181845
type Apply (&&@#@$) (a6989586621679122836 :: Bool) 
Instance details

Defined in Data.Bool.Singletons

type Apply (&&@#@$) (a6989586621679122836 :: Bool) = (&&@#@$$) a6989586621679122836
type Apply (||@#@$) (a6989586621679123482 :: Bool) 
Instance details

Defined in Data.Bool.Singletons

type Apply (||@#@$) (a6989586621679123482 :: Bool) = (||@#@$$) a6989586621679123482
type Apply TFHelper_6989586621679131019Sym0 (a6989586621679131024 :: Bool) 
Instance details

Defined in Data.Eq.Singletons

type Apply TFHelper_6989586621679131019Sym0 (a6989586621679131024 :: Bool) = TFHelper_6989586621679131019Sym1 a6989586621679131024
type Apply ShowsPrec_6989586621680071834Sym0 (a6989586621680071844 :: Nat) 
Instance details

Defined in Text.Show.Singletons

type Apply ShowsPrec_6989586621680071834Sym0 (a6989586621680071844 :: Nat) = ShowsPrec_6989586621680071834Sym1 a6989586621680071844
type Apply (<=?@#@$) (a6989586621679462422 :: Nat) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Apply (<=?@#@$) (a6989586621679462422 :: Nat) = (<=?@#@$$) a6989586621679462422
type Apply (ShowsPrec_6989586621680071834Sym1 a6989586621680071844 :: TyFun Bool (Symbol ~> Symbol) -> Type) (a6989586621680071845 :: Bool) 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsPrec_6989586621680071834Sym1 a6989586621680071844 :: TyFun Bool (Symbol ~> Symbol) -> Type) (a6989586621680071845 :: Bool) = ShowsPrec_6989586621680071834Sym2 a6989586621680071844 a6989586621680071845
type Apply (UnlessSym0 :: TyFun Bool (f () ~> f ()) -> Type) (a6989586621680892589 :: Bool) 
Instance details

Defined in Control.Monad.Singletons

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

Defined in Control.Monad.Singletons.Internal

type Apply (WhenSym0 :: TyFun Bool (f () ~> f ()) -> Type) (a6989586621679286971 :: Bool) = WhenSym1 a6989586621679286971 :: TyFun (f ()) (f ()) -> Type
type Apply (IfSym0 :: TyFun Bool (k ~> (k ~> k)) -> Type) (a6989586621679124049 :: Bool) 
Instance details

Defined in Data.Bool.Singletons

type Apply (IfSym0 :: TyFun Bool (k ~> (k ~> k)) -> Type) (a6989586621679124049 :: Bool) = IfSym1 a6989586621679124049 :: TyFun k (k ~> k) -> Type
type Apply (Elem_6989586621680392157Sym0 :: TyFun a (Identity a ~> Bool) -> Type) (a6989586621680392162 :: a) 
Instance details

Defined in Data.Functor.Identity.Singletons

type Apply (Elem_6989586621680392157Sym0 :: TyFun a (Identity a ~> Bool) -> Type) (a6989586621680392162 :: a) = Elem_6989586621680392157Sym1 a6989586621680392162
type Apply (Elem_6989586621680194236Sym0 :: TyFun a (Proxy a ~> Bool) -> Type) (a6989586621680194241 :: a) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Elem_6989586621680194236Sym0 :: TyFun a (Proxy a ~> Bool) -> Type) (a6989586621680194241 :: a) = Elem_6989586621680194236Sym1 a6989586621680194241
type Apply (Elem_6989586621680194268Sym0 :: TyFun a (Dual a ~> Bool) -> Type) (a6989586621680194277 :: a) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Elem_6989586621680194268Sym0 :: TyFun a (Dual a ~> Bool) -> Type) (a6989586621680194277 :: a) = Elem_6989586621680194268Sym1 a6989586621680194277
type Apply (Elem_6989586621680194618Sym0 :: TyFun a (Product a ~> Bool) -> Type) (a6989586621680194627 :: a) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Elem_6989586621680194618Sym0 :: TyFun a (Product a ~> Bool) -> Type) (a6989586621680194627 :: a) = Elem_6989586621680194618Sym1 a6989586621680194627
type Apply (Elem_6989586621680194443Sym0 :: TyFun a (Sum a ~> Bool) -> Type) (a6989586621680194452 :: a) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Elem_6989586621680194443Sym0 :: TyFun a (Sum a ~> Bool) -> Type) (a6989586621680194452 :: a) = Elem_6989586621680194443Sym1 a6989586621680194452
type Apply (Elem_6989586621680193860Sym0 :: TyFun a ([a] ~> Bool) -> Type) (a6989586621680193869 :: a) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Elem_6989586621680193860Sym0 :: TyFun a ([a] ~> Bool) -> Type) (a6989586621680193869 :: a) = Elem_6989586621680193860Sym1 a6989586621680193869
type Apply (ElemSym0 :: TyFun a ([a] ~> Bool) -> Type) (a6989586621679731822 :: a) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ElemSym0 :: TyFun a ([a] ~> Bool) -> Type) (a6989586621679731822 :: a) = ElemSym1 a6989586621679731822
type Apply (NotElemSym0 :: TyFun a ([a] ~> Bool) -> Type) (a6989586621679731814 :: a) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (NotElemSym0 :: TyFun a ([a] ~> Bool) -> Type) (a6989586621679731814 :: a) = NotElemSym1 a6989586621679731814
type Apply (ListelemSym0 :: TyFun a ([a] ~> Bool) -> Type) (a6989586621680002068 :: a) 
Instance details

Defined in Data.List.Singletons.Internal.Disambiguation

type Apply (ListelemSym0 :: TyFun a ([a] ~> Bool) -> Type) (a6989586621680002068 :: a) = ListelemSym1 a6989586621680002068
type Apply (Bool_Sym0 :: TyFun a (a ~> (Bool ~> a)) -> Type) (a6989586621679120954 :: a) 
Instance details

Defined in Data.Bool.Singletons

type Apply (Bool_Sym0 :: TyFun a (a ~> (Bool ~> a)) -> Type) (a6989586621679120954 :: a) = Bool_Sym1 a6989586621679120954
type Apply ((/=@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679127813 :: a) 
Instance details

Defined in Data.Eq.Singletons

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

Defined in Data.Eq.Singletons

type Apply ((==@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679127808 :: a) = (==@#@$$) a6989586621679127808
type Apply (TFHelper_6989586621679127817Sym0 :: TyFun a (a ~> Bool) -> Type) (a6989586621679127822 :: a) 
Instance details

Defined in Data.Eq.Singletons

type Apply (TFHelper_6989586621679127817Sym0 :: TyFun a (a ~> Bool) -> Type) (a6989586621679127822 :: a) = TFHelper_6989586621679127817Sym1 a6989586621679127822
type Apply (TFHelper_6989586621679127828Sym0 :: TyFun a (a ~> Bool) -> Type) (a6989586621679127833 :: a) 
Instance details

Defined in Data.Eq.Singletons

type Apply (TFHelper_6989586621679127828Sym0 :: TyFun a (a ~> Bool) -> Type) (a6989586621679127833 :: a) = TFHelper_6989586621679127828Sym1 a6989586621679127833
type Apply ((<=@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679166108 :: a) 
Instance details

Defined in Data.Ord.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Ord.Singletons

type Apply ((>@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679166113 :: a) = (>@#@$$) a6989586621679166113
type Apply (TFHelper_6989586621679166153Sym0 :: TyFun a (a ~> Bool) -> Type) (a6989586621679166158 :: a) 
Instance details

Defined in Data.Ord.Singletons

type Apply (TFHelper_6989586621679166153Sym0 :: TyFun a (a ~> Bool) -> Type) (a6989586621679166158 :: a) = TFHelper_6989586621679166153Sym1 a6989586621679166158
type Apply (TFHelper_6989586621679166169Sym0 :: TyFun a (a ~> Bool) -> Type) (a6989586621679166174 :: a) 
Instance details

Defined in Data.Ord.Singletons

type Apply (TFHelper_6989586621679166169Sym0 :: TyFun a (a ~> Bool) -> Type) (a6989586621679166174 :: a) = TFHelper_6989586621679166169Sym1 a6989586621679166174
type Apply (TFHelper_6989586621679166185Sym0 :: TyFun a (a ~> Bool) -> Type) (a6989586621679166190 :: a) 
Instance details

Defined in Data.Ord.Singletons

type Apply (TFHelper_6989586621679166185Sym0 :: TyFun a (a ~> Bool) -> Type) (a6989586621679166190 :: a) = TFHelper_6989586621679166185Sym1 a6989586621679166190
type Apply (TFHelper_6989586621679166201Sym0 :: TyFun a (a ~> Bool) -> Type) (a6989586621679166206 :: a) 
Instance details

Defined in Data.Ord.Singletons

type Apply (TFHelper_6989586621679166201Sym0 :: TyFun a (a ~> Bool) -> Type) (a6989586621679166206 :: a) = TFHelper_6989586621679166201Sym1 a6989586621679166206
type Apply (DefaultEqSym0 :: TyFun k (k ~> Bool) -> Type) (a6989586621679130155 :: k) 
Instance details

Defined in Data.Eq.Singletons

type Apply (DefaultEqSym0 :: TyFun k (k ~> Bool) -> Type) (a6989586621679130155 :: k) = DefaultEqSym1 a6989586621679130155
type Apply (Let6989586621680184051Scrutinee_6989586621680184015Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621680184046 :: k1) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Let6989586621680184051Scrutinee_6989586621680184015Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621680184046 :: k1) = Let6989586621680184051Scrutinee_6989586621680184015Sym1 x6989586621680184046
type Apply (Let6989586621680184075Scrutinee_6989586621680184017Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621680184070 :: k1) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Let6989586621680184075Scrutinee_6989586621680184017Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621680184070 :: k1) = Let6989586621680184075Scrutinee_6989586621680184017Sym1 x6989586621680184070
type Apply (Let6989586621679166141Scrutinee_6989586621679163721Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679166139 :: k1) 
Instance details

Defined in Data.Ord.Singletons

type Apply (Let6989586621679166141Scrutinee_6989586621679163721Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679166139 :: k1) = Let6989586621679166141Scrutinee_6989586621679163721Sym1 x6989586621679166139
type Apply (Let6989586621679166145Scrutinee_6989586621679163723Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679166139 :: k1) 
Instance details

Defined in Data.Ord.Singletons

type Apply (Let6989586621679166145Scrutinee_6989586621679163723Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679166139 :: k1) = Let6989586621679166145Scrutinee_6989586621679163723Sym1 x6989586621679166139
type Apply (Let6989586621679166226Scrutinee_6989586621679163733Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679166224 :: k1) 
Instance details

Defined in Data.Ord.Singletons

type Apply (Let6989586621679166226Scrutinee_6989586621679163733Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679166224 :: k1) = Let6989586621679166226Scrutinee_6989586621679163733Sym1 x6989586621679166224
type Apply (Let6989586621679166242Scrutinee_6989586621679163735Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679166240 :: k1) 
Instance details

Defined in Data.Ord.Singletons

type Apply (Let6989586621679166242Scrutinee_6989586621679163735Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679166240 :: k1) = Let6989586621679166242Scrutinee_6989586621679163735Sym1 x6989586621679166240
type Apply (Bool_Sym1 a6989586621679120954 :: TyFun a (Bool ~> a) -> Type) (a6989586621679120955 :: a) 
Instance details

Defined in Data.Bool.Singletons

type Apply (Bool_Sym1 a6989586621679120954 :: TyFun a (Bool ~> a) -> Type) (a6989586621679120955 :: a) = Bool_Sym2 a6989586621679120954 a6989586621679120955
type Apply (Elem_bySym1 a6989586621679731050 :: TyFun a ([a] ~> Bool) -> Type) (a6989586621679731051 :: a) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Elem_bySym1 a6989586621679731050 :: TyFun a ([a] ~> Bool) -> Type) (a6989586621679731051 :: a) = Elem_bySym2 a6989586621679731050 a6989586621679731051
type Apply (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621680193550 :: a) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621680193550 :: a) = ElemSym1 a6989586621680193550 :: TyFun (t a) Bool -> Type
type Apply (Elem_6989586621680193750Sym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621680193759 :: a) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Elem_6989586621680193750Sym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621680193759 :: a) = Elem_6989586621680193750Sym1 a6989586621680193759 :: TyFun (t a) Bool -> Type
type Apply (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621680193297 :: a) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621680193297 :: a) = NotElemSym1 a6989586621680193297 :: TyFun (t a) Bool -> Type
type Apply (Let6989586621679731119Scrutinee_6989586621679727564Sym0 :: TyFun k1 (TyFun k Bool -> Type) -> Type) (n6989586621679731117 :: k1) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Let6989586621679731119Scrutinee_6989586621679727564Sym0 :: TyFun k1 (TyFun k Bool -> Type) -> Type) (n6989586621679731117 :: k1) = Let6989586621679731119Scrutinee_6989586621679727564Sym1 n6989586621679731117 :: TyFun k Bool -> Type
type Apply (Let6989586621679731363Scrutinee_6989586621679727542Sym0 :: TyFun k1 (TyFun [a] (TyFun (k1 ~> Bool) (TyFun k Bool -> Type) -> Type) -> Type) -> Type) (x6989586621679731361 :: k1) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Let6989586621679731363Scrutinee_6989586621679727542Sym0 :: TyFun k1 (TyFun [a] (TyFun (k1 ~> Bool) (TyFun k Bool -> Type) -> Type) -> Type) -> Type) (x6989586621679731361 :: k1) = Let6989586621679731363Scrutinee_6989586621679727542Sym1 x6989586621679731361 :: TyFun [a] (TyFun (k1 ~> Bool) (TyFun k Bool -> Type) -> Type) -> Type
type Apply (Let6989586621679731185Scrutinee_6989586621679727560Sym0 :: TyFun k1 (TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) (key6989586621679731181 :: k1) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Let6989586621679731185Scrutinee_6989586621679727560Sym0 :: TyFun k1 (TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) (key6989586621679731181 :: k1) = Let6989586621679731185Scrutinee_6989586621679727560Sym1 key6989586621679731181 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type
type Apply (Let6989586621679731071Scrutinee_6989586621679727570Sym0 :: TyFun k1 (TyFun k2 (TyFun [k1] (TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (y6989586621679731068 :: k1) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Let6989586621679731071Scrutinee_6989586621679727570Sym0 :: TyFun k1 (TyFun k2 (TyFun [k1] (TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (y6989586621679731068 :: k1) = Let6989586621679731071Scrutinee_6989586621679727570Sym1 y6989586621679731068 :: TyFun k2 (TyFun [k1] (TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679731087Scrutinee_6989586621679727568Sym0 :: TyFun k1 (TyFun k2 (TyFun [k1] (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) (x6989586621679731084 :: k1) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Let6989586621679731087Scrutinee_6989586621679727568Sym0 :: TyFun k1 (TyFun k2 (TyFun [k1] (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) (x6989586621679731084 :: k1) = Let6989586621679731087Scrutinee_6989586621679727568Sym1 x6989586621679731084 :: TyFun k2 (TyFun [k1] (TyFun k3 Bool -> Type) -> Type) -> Type
type Apply (Lambda_6989586621680892729Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun Bool ([k1] ~> [k1]) -> Type) -> Type) -> Type) -> Type) (x6989586621680892728 :: k1) 
Instance details

Defined in Control.Monad.Singletons

type Apply (Lambda_6989586621680892729Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun Bool ([k1] ~> [k1]) -> Type) -> Type) -> Type) -> Type) (x6989586621680892728 :: k1) = Lambda_6989586621680892729Sym1 x6989586621680892728 :: TyFun k2 (TyFun k3 (TyFun Bool ([k1] ~> [k1]) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621680193722Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (a_69895866216801937166989586621680193721 :: k1) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Lambda_6989586621680193722Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (a_69895866216801937166989586621680193721 :: k1) = Lambda_6989586621680193722Sym1 a_69895866216801937166989586621680193721 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type
type Apply (Let6989586621679731100Scrutinee_6989586621679727566Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (x6989586621679731097 :: k1) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Let6989586621679731100Scrutinee_6989586621679727566Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (x6989586621679731097 :: k1) = Let6989586621679731100Scrutinee_6989586621679727566Sym1 x6989586621679731097 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type
type Apply (Let6989586621679731262Scrutinee_6989586621679727550Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (n6989586621679731259 :: k1) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Let6989586621679731262Scrutinee_6989586621679727550Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (n6989586621679731259 :: k1) = Let6989586621679731262Scrutinee_6989586621679727550Sym1 n6989586621679731259 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type
type Apply (Let6989586621679731275Scrutinee_6989586621679727548Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (n6989586621679731272 :: k1) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Let6989586621679731275Scrutinee_6989586621679727548Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (n6989586621679731272 :: k1) = Let6989586621679731275Scrutinee_6989586621679727548Sym1 n6989586621679731272 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type
type Apply (Let6989586621679516447Scrutinee_6989586621679516255Sym0 :: TyFun k1 (TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (x6989586621679516446 :: k1) 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (Let6989586621679516447Scrutinee_6989586621679516255Sym0 :: TyFun k1 (TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (x6989586621679516446 :: k1) = Let6989586621679516447Scrutinee_6989586621679516255Sym1 x6989586621679516446 :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679731185Scrutinee_6989586621679727560Sym1 key6989586621679731181 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (x6989586621679731182 :: k1) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Let6989586621679731185Scrutinee_6989586621679727560Sym1 key6989586621679731181 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (x6989586621679731182 :: k1) = Let6989586621679731185Scrutinee_6989586621679727560Sym2 key6989586621679731181 x6989586621679731182 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type
type Apply (Let6989586621679731071Scrutinee_6989586621679727570Sym1 y6989586621679731068 :: TyFun k2 (TyFun [k1] (TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) (ys6989586621679731069 :: k2) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Let6989586621679731071Scrutinee_6989586621679727570Sym1 y6989586621679731068 :: TyFun k2 (TyFun [k1] (TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) (ys6989586621679731069 :: k2) = Let6989586621679731071Scrutinee_6989586621679727570Sym2 y6989586621679731068 ys6989586621679731069 :: TyFun [k1] (TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type) -> Type
type Apply (Let6989586621679731087Scrutinee_6989586621679727568Sym1 x6989586621679731084 :: TyFun k2 (TyFun [k1] (TyFun k3 Bool -> Type) -> Type) -> Type) (xs6989586621679731085 :: k2) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Let6989586621679731087Scrutinee_6989586621679727568Sym1 x6989586621679731084 :: TyFun k2 (TyFun [k1] (TyFun k3 Bool -> Type) -> Type) -> Type) (xs6989586621679731085 :: k2) = Let6989586621679731087Scrutinee_6989586621679727568Sym2 x6989586621679731084 xs6989586621679731085 :: TyFun [k1] (TyFun k3 Bool -> Type) -> Type
type Apply (Lambda_6989586621680892729Sym1 x6989586621680892728 :: TyFun k2 (TyFun k3 (TyFun Bool ([k1] ~> [k1]) -> Type) -> Type) -> Type) (p6989586621680892724 :: k2) 
Instance details

Defined in Control.Monad.Singletons

type Apply (Lambda_6989586621680892729Sym1 x6989586621680892728 :: TyFun k2 (TyFun k3 (TyFun Bool ([k1] ~> [k1]) -> Type) -> Type) -> Type) (p6989586621680892724 :: k2) = Lambda_6989586621680892729Sym2 x6989586621680892728 p6989586621680892724 :: TyFun k3 (TyFun Bool ([k1] ~> [k1]) -> Type) -> Type
type Apply (Lambda_6989586621680193722Sym1 a_69895866216801937166989586621680193721 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) (arg_69895866216801931086989586621680193724 :: k2) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Lambda_6989586621680193722Sym1 a_69895866216801937166989586621680193721 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) (arg_69895866216801931086989586621680193724 :: k2) = Lambda_6989586621680193722Sym2 a_69895866216801937166989586621680193721 arg_69895866216801931086989586621680193724 :: TyFun k3 Bool -> Type
type Apply (Let6989586621679731100Scrutinee_6989586621679727566Sym1 x6989586621679731097 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) (xs6989586621679731098 :: k2) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Let6989586621679731100Scrutinee_6989586621679727566Sym1 x6989586621679731097 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) (xs6989586621679731098 :: k2) = Let6989586621679731100Scrutinee_6989586621679727566Sym2 x6989586621679731097 xs6989586621679731098 :: TyFun k3 Bool -> Type
type Apply (Let6989586621679731262Scrutinee_6989586621679727550Sym1 n6989586621679731259 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) (x6989586621679731260 :: k2) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Let6989586621679731262Scrutinee_6989586621679727550Sym1 n6989586621679731259 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) (x6989586621679731260 :: k2) = Let6989586621679731262Scrutinee_6989586621679727550Sym2 n6989586621679731259 x6989586621679731260 :: TyFun k3 Bool -> Type
type Apply (Let6989586621679731275Scrutinee_6989586621679727548Sym1 n6989586621679731272 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) (x6989586621679731273 :: k2) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Let6989586621679731275Scrutinee_6989586621679727548Sym1 n6989586621679731272 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) (x6989586621679731273 :: k2) = Let6989586621679731275Scrutinee_6989586621679727548Sym2 n6989586621679731272 x6989586621679731273 :: TyFun k3 Bool -> Type
type Apply (Let6989586621679516356Scrutinee_6989586621679516279Sym0 :: TyFun k1 (TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (x16989586621679516351 :: k1) 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (Let6989586621679516356Scrutinee_6989586621679516279Sym0 :: TyFun k1 (TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (x16989586621679516351 :: k1) = Let6989586621679516356Scrutinee_6989586621679516279Sym1 x16989586621679516351 :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679516393Scrutinee_6989586621679516269Sym0 :: TyFun k1 (TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (x16989586621679516388 :: k1) 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (Let6989586621679516393Scrutinee_6989586621679516269Sym0 :: TyFun k1 (TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (x16989586621679516388 :: k1) = Let6989586621679516393Scrutinee_6989586621679516269Sym1 x16989586621679516388 :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679516447Scrutinee_6989586621679516255Sym1 x6989586621679516446 :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) (x06989586621679516441 :: k2) 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (Let6989586621679516447Scrutinee_6989586621679516255Sym1 x6989586621679516446 :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) (x06989586621679516441 :: k2) = Let6989586621679516447Scrutinee_6989586621679516255Sym2 x6989586621679516446 x06989586621679516441 :: TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type
type Apply (Let6989586621679731185Scrutinee_6989586621679727560Sym2 key6989586621679731181 x6989586621679731182 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) (y6989586621679731183 :: k2) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Let6989586621679731185Scrutinee_6989586621679727560Sym2 key6989586621679731181 x6989586621679731182 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) (y6989586621679731183 :: k2) = Let6989586621679731185Scrutinee_6989586621679727560Sym3 key6989586621679731181 x6989586621679731182 y6989586621679731183 :: TyFun k3 Bool -> Type
type Apply (Lambda_6989586621680892729Sym2 x6989586621680892728 p6989586621680892724 :: TyFun k3 (TyFun Bool ([k1] ~> [k1]) -> Type) -> Type) (a_69895866216808927176989586621680892725 :: k3) 
Instance details

Defined in Control.Monad.Singletons

type Apply (Lambda_6989586621680892729Sym2 x6989586621680892728 p6989586621680892724 :: TyFun k3 (TyFun Bool ([k1] ~> [k1]) -> Type) -> Type) (a_69895866216808927176989586621680892725 :: k3) = Lambda_6989586621680892729Sym3 x6989586621680892728 p6989586621680892724 a_69895866216808927176989586621680892725
type Apply (Lambda_6989586621680892729Sym3 x6989586621680892728 p6989586621680892724 a_69895866216808927176989586621680892725 :: TyFun Bool ([k1] ~> [k1]) -> Type) (flg6989586621680892731 :: Bool) 
Instance details

Defined in Control.Monad.Singletons

type Apply (Lambda_6989586621680892729Sym3 x6989586621680892728 p6989586621680892724 a_69895866216808927176989586621680892725 :: TyFun Bool ([k1] ~> [k1]) -> Type) (flg6989586621680892731 :: Bool) = Lambda_6989586621680892729 x6989586621680892728 p6989586621680892724 a_69895866216808927176989586621680892725 flg6989586621680892731
type Apply (Let6989586621679516447Scrutinee_6989586621679516255Sym2 x6989586621679516446 x06989586621679516441 :: TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) (y6989586621679516442 :: k1) 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (Let6989586621679516447Scrutinee_6989586621679516255Sym2 x6989586621679516446 x06989586621679516441 :: TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) (y6989586621679516442 :: k1) = Let6989586621679516447Scrutinee_6989586621679516255Sym3 x6989586621679516446 x06989586621679516441 y6989586621679516442 :: TyFun k3 (TyFun k4 Bool -> Type) -> Type
type Apply (Let6989586621679516356Scrutinee_6989586621679516279Sym1 x16989586621679516351 :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (x26989586621679516352 :: k2) 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (Let6989586621679516356Scrutinee_6989586621679516279Sym1 x16989586621679516351 :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (x26989586621679516352 :: k2) = Let6989586621679516356Scrutinee_6989586621679516279Sym2 x16989586621679516351 x26989586621679516352 :: TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679516393Scrutinee_6989586621679516269Sym1 x16989586621679516388 :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (x26989586621679516389 :: k2) 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (Let6989586621679516393Scrutinee_6989586621679516269Sym1 x16989586621679516388 :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (x26989586621679516389 :: k2) = Let6989586621679516393Scrutinee_6989586621679516269Sym2 x16989586621679516388 x26989586621679516389 :: TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679516356Scrutinee_6989586621679516279Sym2 x16989586621679516351 x26989586621679516352 :: TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) (y6989586621679516353 :: k1) 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (Let6989586621679516356Scrutinee_6989586621679516279Sym2 x16989586621679516351 x26989586621679516352 :: TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) (y6989586621679516353 :: k1) = Let6989586621679516356Scrutinee_6989586621679516279Sym3 x16989586621679516351 x26989586621679516352 y6989586621679516353 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type
type Apply (Let6989586621679516393Scrutinee_6989586621679516269Sym2 x16989586621679516388 x26989586621679516389 :: TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) (y6989586621679516390 :: k1) 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (Let6989586621679516393Scrutinee_6989586621679516269Sym2 x16989586621679516388 x26989586621679516389 :: TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) (y6989586621679516390 :: k1) = Let6989586621679516393Scrutinee_6989586621679516269Sym3 x16989586621679516388 x26989586621679516389 y6989586621679516390 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type
type Apply (Let6989586621679516447Scrutinee_6989586621679516255Sym3 x6989586621679516446 x06989586621679516441 y6989586621679516442 :: TyFun k3 (TyFun k4 Bool -> Type) -> Type) (arg_69895866216795162516989586621679516437 :: k3) 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (Let6989586621679516447Scrutinee_6989586621679516255Sym3 x6989586621679516446 x06989586621679516441 y6989586621679516442 :: TyFun k3 (TyFun k4 Bool -> Type) -> Type) (arg_69895866216795162516989586621679516437 :: k3) = Let6989586621679516447Scrutinee_6989586621679516255Sym4 x6989586621679516446 x06989586621679516441 y6989586621679516442 arg_69895866216795162516989586621679516437 :: TyFun k4 Bool -> Type
type Apply (Let6989586621679516356Scrutinee_6989586621679516279Sym3 x16989586621679516351 x26989586621679516352 y6989586621679516353 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) (arg_69895866216795162736989586621679516346 :: k3) 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (Let6989586621679516356Scrutinee_6989586621679516279Sym3 x16989586621679516351 x26989586621679516352 y6989586621679516353 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) (arg_69895866216795162736989586621679516346 :: k3) = Let6989586621679516356Scrutinee_6989586621679516279Sym4 x16989586621679516351 x26989586621679516352 y6989586621679516353 arg_69895866216795162736989586621679516346 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type
type Apply (Let6989586621679516393Scrutinee_6989586621679516269Sym3 x16989586621679516388 x26989586621679516389 y6989586621679516390 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) (arg_69895866216795162636989586621679516383 :: k3) 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (Let6989586621679516393Scrutinee_6989586621679516269Sym3 x16989586621679516388 x26989586621679516389 y6989586621679516390 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) (arg_69895866216795162636989586621679516383 :: k3) = Let6989586621679516393Scrutinee_6989586621679516269Sym4 x16989586621679516388 x26989586621679516389 y6989586621679516390 arg_69895866216795162636989586621679516383 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type
type Apply (Let6989586621679516356Scrutinee_6989586621679516279Sym4 x16989586621679516351 x26989586621679516352 y6989586621679516353 arg_69895866216795162736989586621679516346 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type) (arg_69895866216795162756989586621679516347 :: k4) 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (Let6989586621679516356Scrutinee_6989586621679516279Sym4 x16989586621679516351 x26989586621679516352 y6989586621679516353 arg_69895866216795162736989586621679516346 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type) (arg_69895866216795162756989586621679516347 :: k4) = Let6989586621679516356Scrutinee_6989586621679516279Sym5 x16989586621679516351 x26989586621679516352 y6989586621679516353 arg_69895866216795162736989586621679516346 arg_69895866216795162756989586621679516347 :: TyFun k5 Bool -> Type
type Apply (Let6989586621679516393Scrutinee_6989586621679516269Sym4 x16989586621679516388 x26989586621679516389 y6989586621679516390 arg_69895866216795162636989586621679516383 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type) (arg_69895866216795162656989586621679516384 :: k4) 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (Let6989586621679516393Scrutinee_6989586621679516269Sym4 x16989586621679516388 x26989586621679516389 y6989586621679516390 arg_69895866216795162636989586621679516383 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type) (arg_69895866216795162656989586621679516384 :: k4) = Let6989586621679516393Scrutinee_6989586621679516269Sym5 x16989586621679516388 x26989586621679516389 y6989586621679516390 arg_69895866216795162636989586621679516383 arg_69895866216795162656989586621679516384 :: TyFun k5 Bool -> Type
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 (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 (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 (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 (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 (IsInfixOf xs ys :: Bool -> Type) 
Instance details

Defined in Fcf.Data.List

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

Defined in Fcf.Data.List

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

Defined in Fcf.Data.List

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

Defined in Fcf.Class.Foldable

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

Defined in Fcf.Class.Foldable

type Eval (Any p lst :: Bool -> Type) = Eval (Foldr (Bicomap p (Pure :: Bool -> Bool -> Type) (||)) 'False lst)
type Eval (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 Morley.Util.Fcf

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

Defined in Data.List.Singletons.Internal

type Apply AndSym0 (a6989586621679732059 :: [Bool]) = And a6989586621679732059
type Apply OrSym0 (a6989586621679732054 :: [Bool]) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply OrSym0 (a6989586621679732054 :: [Bool]) = Or a6989586621679732054
type Apply (Null_6989586621680392273Sym0 :: TyFun (Identity a) Bool -> Type) (a6989586621680392277 :: Identity a) 
Instance details

Defined in Data.Functor.Identity.Singletons

type Apply (Null_6989586621680392273Sym0 :: TyFun (Identity a) Bool -> Type) (a6989586621680392277 :: Identity a) = Null_6989586621680392273 a6989586621680392277
type Apply (Null_6989586621680194400Sym0 :: TyFun (Dual a) Bool -> Type) (a6989586621680194404 :: Dual a) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Null_6989586621680194400Sym0 :: TyFun (Dual a) Bool -> Type) (a6989586621680194404 :: Dual a) = Null_6989586621680194400 a6989586621680194404
type Apply (Null_6989586621680194750Sym0 :: TyFun (Product a) Bool -> Type) (a6989586621680194754 :: Product a) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Null_6989586621680194750Sym0 :: TyFun (Product a) Bool -> Type) (a6989586621680194754 :: Product a) = Null_6989586621680194750 a6989586621680194754
type Apply (Null_6989586621680194575Sym0 :: TyFun (Sum a) Bool -> Type) (a6989586621680194579 :: Sum a) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Null_6989586621680194575Sym0 :: TyFun (Sum a) Bool -> Type) (a6989586621680194579 :: Sum a) = Null_6989586621680194575 a6989586621680194579
type Apply (IsJustSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679486210 :: Maybe a) 
Instance details

Defined in Data.Maybe.Singletons

type Apply (IsJustSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679486210 :: Maybe a) = IsJust a6989586621679486210
type Apply (IsNothingSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679486207 :: Maybe a) 
Instance details

Defined in Data.Maybe.Singletons

type Apply (IsNothingSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679486207 :: Maybe a) = IsNothing a6989586621679486207
type Apply (Null_6989586621680193994Sym0 :: TyFun [a] Bool -> Type) (a6989586621680194000 :: [a]) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Null_6989586621680193994Sym0 :: TyFun [a] Bool -> Type) (a6989586621680194000 :: [a]) = Null_6989586621680193994 a6989586621680194000
type Apply (NullSym0 :: TyFun [a] Bool -> Type) (a6989586621679732232 :: [a]) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (NullSym0 :: TyFun [a] Bool -> Type) (a6989586621679732232 :: [a]) = Null a6989586621679732232
type Apply (ListnullSym0 :: TyFun [a] Bool -> Type) (a6989586621680001977 :: [a]) 
Instance details

Defined in Data.List.Singletons.Internal.Disambiguation

type Apply (ListnullSym0 :: TyFun [a] Bool -> Type) (a6989586621680001977 :: [a]) = Listnull a6989586621680001977
type Apply (AndSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680193369 :: t Bool) 
Instance details

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

type Apply (OrSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680193363 :: t Bool) = Or a6989586621680193363
type Apply (TFHelper_6989586621679131006Sym1 a6989586621679131011 :: TyFun (Identity a) Bool -> Type) (a6989586621679131012 :: Identity a) 
Instance details

Defined in Data.Eq.Singletons

type Apply (TFHelper_6989586621679131006Sym1 a6989586621679131011 :: TyFun (Identity a) Bool -> Type) (a6989586621679131012 :: Identity a) = TFHelper_6989586621679131006 a6989586621679131011 a6989586621679131012
type Apply (Elem_6989586621680392157Sym1 a6989586621680392162 :: TyFun (Identity a) Bool -> Type) (a6989586621680392163 :: Identity a) 
Instance details

Defined in Data.Functor.Identity.Singletons

type Apply (Elem_6989586621680392157Sym1 a6989586621680392162 :: TyFun (Identity a) Bool -> Type) (a6989586621680392163 :: Identity a) = Elem_6989586621680392157 a6989586621680392162 a6989586621680392163
type Apply (TFHelper_6989586621680109664Sym1 a6989586621680109669 :: TyFun (First a) Bool -> Type) (a6989586621680109670 :: First a) 
Instance details

Defined in Data.Monoid.Singletons

type Apply (TFHelper_6989586621680109664Sym1 a6989586621680109669 :: TyFun (First a) Bool -> Type) (a6989586621680109670 :: First a) = TFHelper_6989586621680109664 a6989586621680109669 a6989586621680109670
type Apply (TFHelper_6989586621680109684Sym1 a6989586621680109689 :: TyFun (Last a) Bool -> Type) (a6989586621680109690 :: Last a) 
Instance details

Defined in Data.Monoid.Singletons

type Apply (TFHelper_6989586621680109684Sym1 a6989586621680109689 :: TyFun (Last a) Bool -> Type) (a6989586621680109690 :: Last a) = TFHelper_6989586621680109684 a6989586621680109689 a6989586621680109690
type Apply (TFHelper_6989586621679179231Sym1 a6989586621679179236 :: TyFun (Down a) Bool -> Type) (a6989586621679179237 :: Down a) 
Instance details

Defined in Data.Ord.Singletons

type Apply (TFHelper_6989586621679179231Sym1 a6989586621679179236 :: TyFun (Down a) Bool -> Type) (a6989586621679179237 :: Down a) = TFHelper_6989586621679179231 a6989586621679179236 a6989586621679179237
type Apply (TFHelper_6989586621679606240Sym1 a6989586621679606245 :: TyFun (First a) Bool -> Type) (a6989586621679606246 :: First a) 
Instance details

Defined in Data.Semigroup.Singletons.Internal

type Apply (TFHelper_6989586621679606240Sym1 a6989586621679606245 :: TyFun (First a) Bool -> Type) (a6989586621679606246 :: First a) = TFHelper_6989586621679606240 a6989586621679606245 a6989586621679606246
type Apply (TFHelper_6989586621679606260Sym1 a6989586621679606265 :: TyFun (Last a) Bool -> Type) (a6989586621679606266 :: Last a) 
Instance details

Defined in Data.Semigroup.Singletons.Internal

type Apply (TFHelper_6989586621679606260Sym1 a6989586621679606265 :: TyFun (Last a) Bool -> Type) (a6989586621679606266 :: Last a) = TFHelper_6989586621679606260 a6989586621679606265 a6989586621679606266
type Apply (TFHelper_6989586621679606220Sym1 a6989586621679606225 :: TyFun (Max a) Bool -> Type) (a6989586621679606226 :: Max a) 
Instance details

Defined in Data.Semigroup.Singletons.Internal

type Apply (TFHelper_6989586621679606220Sym1 a6989586621679606225 :: TyFun (Max a) Bool -> Type) (a6989586621679606226 :: Max a) = TFHelper_6989586621679606220 a6989586621679606225 a6989586621679606226
type Apply (TFHelper_6989586621679606200Sym1 a6989586621679606205 :: TyFun (Min a) Bool -> Type) (a6989586621679606206 :: Min a) 
Instance details

Defined in Data.Semigroup.Singletons.Internal

type Apply (TFHelper_6989586621679606200Sym1 a6989586621679606205 :: TyFun (Min a) Bool -> Type) (a6989586621679606206 :: Min a) = TFHelper_6989586621679606200 a6989586621679606205 a6989586621679606206
type Apply (TFHelper_6989586621679606280Sym1 a6989586621679606285 :: TyFun (WrappedMonoid m) Bool -> Type) (a6989586621679606286 :: WrappedMonoid m) 
Instance details

Defined in Data.Semigroup.Singletons.Internal

type Apply (TFHelper_6989586621679606280Sym1 a6989586621679606285 :: TyFun (WrappedMonoid m) Bool -> Type) (a6989586621679606286 :: WrappedMonoid m) = TFHelper_6989586621679606280 a6989586621679606285 a6989586621679606286
type Apply (Elem_6989586621680194268Sym1 a6989586621680194277 :: TyFun (Dual a) Bool -> Type) (a6989586621680194278 :: Dual a) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Elem_6989586621680194268Sym1 a6989586621680194277 :: TyFun (Dual a) Bool -> Type) (a6989586621680194278 :: Dual a) = Elem_6989586621680194268 a6989586621680194277 a6989586621680194278
type Apply (TFHelper_6989586621679606106Sym1 a6989586621679606111 :: TyFun (Dual a) Bool -> Type) (a6989586621679606112 :: Dual a) 
Instance details

Defined in Data.Semigroup.Singletons.Internal

type Apply (TFHelper_6989586621679606106Sym1 a6989586621679606111 :: TyFun (Dual a) Bool -> Type) (a6989586621679606112 :: Dual a) = TFHelper_6989586621679606106 a6989586621679606111 a6989586621679606112
type Apply (Elem_6989586621680194618Sym1 a6989586621680194627 :: TyFun (Product a) Bool -> Type) (a6989586621680194628 :: Product a) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Elem_6989586621680194618Sym1 a6989586621680194627 :: TyFun (Product a) Bool -> Type) (a6989586621680194628 :: Product a) = Elem_6989586621680194618 a6989586621680194627 a6989586621680194628
type Apply (TFHelper_6989586621679606180Sym1 a6989586621679606185 :: TyFun (Product a) Bool -> Type) (a6989586621679606186 :: Product a) 
Instance details

Defined in Data.Semigroup.Singletons.Internal

type Apply (TFHelper_6989586621679606180Sym1 a6989586621679606185 :: TyFun (Product a) Bool -> Type) (a6989586621679606186 :: Product a) = TFHelper_6989586621679606180 a6989586621679606185 a6989586621679606186
type Apply (Elem_6989586621680194443Sym1 a6989586621680194452 :: TyFun (Sum a) Bool -> Type) (a6989586621680194453 :: Sum a) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Elem_6989586621680194443Sym1 a6989586621680194452 :: TyFun (Sum a) Bool -> Type) (a6989586621680194453 :: Sum a) = Elem_6989586621680194443 a6989586621680194452 a6989586621680194453
type Apply (TFHelper_6989586621679606160Sym1 a6989586621679606165 :: TyFun (Sum a) Bool -> Type) (a6989586621679606166 :: Sum a) 
Instance details

Defined in Data.Semigroup.Singletons.Internal

type Apply (TFHelper_6989586621679606160Sym1 a6989586621679606165 :: TyFun (Sum a) Bool -> Type) (a6989586621679606166 :: Sum a) = TFHelper_6989586621679606160 a6989586621679606165 a6989586621679606166
type Apply (TFHelper_6989586621679130622Sym1 a6989586621679130627 :: TyFun (NonEmpty a) Bool -> Type) (a6989586621679130628 :: NonEmpty a) 
Instance details

Defined in Data.Eq.Singletons

type Apply (TFHelper_6989586621679130622Sym1 a6989586621679130627 :: TyFun (NonEmpty a) Bool -> Type) (a6989586621679130628 :: NonEmpty a) = TFHelper_6989586621679130622 a6989586621679130627 a6989586621679130628
type Apply (TFHelper_6989586621679130516Sym1 a6989586621679130521 :: TyFun (Maybe a) Bool -> Type) (a6989586621679130522 :: Maybe a) 
Instance details

Defined in Data.Eq.Singletons

type Apply (TFHelper_6989586621679130516Sym1 a6989586621679130521 :: TyFun (Maybe a) Bool -> Type) (a6989586621679130522 :: Maybe a) = TFHelper_6989586621679130516 a6989586621679130521 a6989586621679130522
type Apply (TFHelper_6989586621679130547Sym1 a6989586621679130552 :: TyFun [a] Bool -> Type) (a6989586621679130553 :: [a]) 
Instance details

Defined in Data.Eq.Singletons

type Apply (TFHelper_6989586621679130547Sym1 a6989586621679130552 :: TyFun [a] Bool -> Type) (a6989586621679130553 :: [a]) = TFHelper_6989586621679130547 a6989586621679130552 a6989586621679130553
type Apply (Elem_6989586621680193860Sym1 a6989586621680193869 :: TyFun [a] Bool -> Type) (a6989586621680193870 :: [a]) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Elem_6989586621680193860Sym1 a6989586621680193869 :: TyFun [a] Bool -> Type) (a6989586621680193870 :: [a]) = Elem_6989586621680193860 a6989586621680193869 a6989586621680193870
type Apply (AllSym1 a6989586621679732047 :: TyFun [a] Bool -> Type) (a6989586621679732048 :: [a]) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (AllSym1 a6989586621679732047 :: TyFun [a] Bool -> Type) (a6989586621679732048 :: [a]) = All a6989586621679732047 a6989586621679732048
type Apply (AnySym1 a6989586621679732039 :: TyFun [a] Bool -> Type) (a6989586621679732040 :: [a]) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (AnySym1 a6989586621679732039 :: TyFun [a] Bool -> Type) (a6989586621679732040 :: [a]) = Any a6989586621679732039 a6989586621679732040
type Apply (ElemSym1 a6989586621679731822 :: TyFun [a] Bool -> Type) (a6989586621679731823 :: [a]) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ElemSym1 a6989586621679731822 :: TyFun [a] Bool -> Type) (a6989586621679731823 :: [a]) = Elem a6989586621679731822 a6989586621679731823
type Apply (IsInfixOfSym1 a6989586621679731830 :: TyFun [a] Bool -> Type) (a6989586621679731831 :: [a]) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IsInfixOfSym1 a6989586621679731830 :: TyFun [a] Bool -> Type) (a6989586621679731831 :: [a]) = IsInfixOf a6989586621679731830 a6989586621679731831
type Apply (IsPrefixOfSym1 a6989586621679731844 :: TyFun [a] Bool -> Type) (a6989586621679731845 :: [a]) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IsPrefixOfSym1 a6989586621679731844 :: TyFun [a] Bool -> Type) (a6989586621679731845 :: [a]) = IsPrefixOf a6989586621679731844 a6989586621679731845
type Apply (IsSuffixOfSym1 a6989586621679731837 :: TyFun [a] Bool -> Type) (a6989586621679731838 :: [a]) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IsSuffixOfSym1 a6989586621679731837 :: TyFun [a] Bool -> Type) (a6989586621679731838 :: [a]) = IsSuffixOf a6989586621679731837 a6989586621679731838
type Apply (NotElemSym1 a6989586621679731814 :: TyFun [a] Bool -> Type) (a6989586621679731815 :: [a]) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (NotElemSym1 a6989586621679731814 :: TyFun [a] Bool -> Type) (a6989586621679731815 :: [a]) = NotElem a6989586621679731814 a6989586621679731815
type Apply (ListelemSym1 a6989586621680002068 :: TyFun [a] Bool -> Type) (a6989586621680002069 :: [a]) 
Instance details

Defined in Data.List.Singletons.Internal.Disambiguation

type Apply (ListelemSym1 a6989586621680002068 :: TyFun [a] Bool -> Type) (a6989586621680002069 :: [a]) = Listelem a6989586621680002068 a6989586621680002069
type Apply (ListisPrefixOfSym1 a6989586621680002140 :: TyFun [a] Bool -> Type) (a6989586621680002141 :: [a]) 
Instance details

Defined in Data.List.Singletons.Internal.Disambiguation

type Apply (ListisPrefixOfSym1 a6989586621680002140 :: TyFun [a] Bool -> Type) (a6989586621680002141 :: [a]) = ListisPrefixOf a6989586621680002140 a6989586621680002141
type Apply (Elem_bySym2 a6989586621679731050 a6989586621679731051 :: TyFun [a] Bool -> Type) (a6989586621679731052 :: [a]) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Elem_bySym2 a6989586621679731050 a6989586621679731051 :: TyFun [a] Bool -> Type) (a6989586621679731052 :: [a]) = Elem_by a6989586621679731050 a6989586621679731051 a6989586621679731052
type Apply (AllSym1 a6989586621680193346 :: TyFun (t a) Bool -> Type) (a6989586621680193347 :: t a) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AllSym1 a6989586621680193346 :: TyFun (t a) Bool -> Type) (a6989586621680193347 :: t a) = All a6989586621680193346 a6989586621680193347
type Apply (AnySym1 a6989586621680193355 :: TyFun (t a) Bool -> Type) (a6989586621680193356 :: t a) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AnySym1 a6989586621680193355 :: TyFun (t a) Bool -> Type) (a6989586621680193356 :: t a) = Any a6989586621680193355 a6989586621680193356
type Apply (ElemSym1 a6989586621680193550 :: TyFun (t a) Bool -> Type) (a6989586621680193551 :: t a) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ElemSym1 a6989586621680193550 :: TyFun (t a) Bool -> Type) (a6989586621680193551 :: t a) = Elem a6989586621680193550 a6989586621680193551
type Apply (Elem_6989586621680193750Sym1 a6989586621680193759 :: TyFun (t a) Bool -> Type) (a6989586621680193760 :: t a) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Elem_6989586621680193750Sym1 a6989586621680193759 :: TyFun (t a) Bool -> Type) (a6989586621680193760 :: t a) = Elem_6989586621680193750 a6989586621680193759 a6989586621680193760
type Apply (NotElemSym1 a6989586621680193297 :: TyFun (t a) Bool -> Type) (a6989586621680193298 :: t a) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (NotElemSym1 a6989586621680193297 :: TyFun (t a) Bool -> Type) (a6989586621680193298 :: t a) = NotElem a6989586621680193297 a6989586621680193298
type Apply (NullSym0 :: TyFun (t a) Bool -> Type) (a6989586621680193543 :: t a) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (NullSym0 :: TyFun (t a) Bool -> Type) (a6989586621680193543 :: t a) = Null a6989586621680193543
type Apply (Null_6989586621680193714Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680193720 :: t a) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Null_6989586621680193714Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680193720 :: t a) = Null_6989586621680193714 a6989586621680193720
type Apply (TFHelper_6989586621679131006Sym0 :: TyFun (Identity a) (Identity a ~> Bool) -> Type) (a6989586621679131011 :: Identity a) 
Instance details

Defined in Data.Eq.Singletons

type Apply (TFHelper_6989586621679131006Sym0 :: TyFun (Identity a) (Identity a ~> Bool) -> Type) (a6989586621679131011 :: Identity a) = TFHelper_6989586621679131006Sym1 a6989586621679131011
type Apply (TFHelper_6989586621680109664Sym0 :: TyFun (First a) (First a ~> Bool) -> Type) (a6989586621680109669 :: First a) 
Instance details

Defined in Data.Monoid.Singletons

type Apply (TFHelper_6989586621680109664Sym0 :: TyFun (First a) (First a ~> Bool) -> Type) (a6989586621680109669 :: First a) = TFHelper_6989586621680109664Sym1 a6989586621680109669
type Apply (TFHelper_6989586621680109684Sym0 :: TyFun (Last a) (Last a ~> Bool) -> Type) (a6989586621680109689 :: Last a) 
Instance details

Defined in Data.Monoid.Singletons

type Apply (TFHelper_6989586621680109684Sym0 :: TyFun (Last a) (Last a ~> Bool) -> Type) (a6989586621680109689 :: Last a) = TFHelper_6989586621680109684Sym1 a6989586621680109689
type Apply (TFHelper_6989586621679179231Sym0 :: TyFun (Down a) (Down a ~> Bool) -> Type) (a6989586621679179236 :: Down a) 
Instance details

Defined in Data.Ord.Singletons

type Apply (TFHelper_6989586621679179231Sym0 :: TyFun (Down a) (Down a ~> Bool) -> Type) (a6989586621679179236 :: Down a) = TFHelper_6989586621679179231Sym1 a6989586621679179236
type Apply (TFHelper_6989586621679606240Sym0 :: TyFun (First a) (First a ~> Bool) -> Type) (a6989586621679606245 :: First a) 
Instance details

Defined in Data.Semigroup.Singletons.Internal

type Apply (TFHelper_6989586621679606240Sym0 :: TyFun (First a) (First a ~> Bool) -> Type) (a6989586621679606245 :: First a) = TFHelper_6989586621679606240Sym1 a6989586621679606245
type Apply (TFHelper_6989586621679606260Sym0 :: TyFun (Last a) (Last a ~> Bool) -> Type) (a6989586621679606265 :: Last a) 
Instance details

Defined in Data.Semigroup.Singletons.Internal

type Apply (TFHelper_6989586621679606260Sym0 :: TyFun (Last a) (Last a ~> Bool) -> Type) (a6989586621679606265 :: Last a) = TFHelper_6989586621679606260Sym1 a6989586621679606265
type Apply (TFHelper_6989586621679606220Sym0 :: TyFun (Max a) (Max a ~> Bool) -> Type) (a6989586621679606225 :: Max a) 
Instance details

Defined in Data.Semigroup.Singletons.Internal

type Apply (TFHelper_6989586621679606220Sym0 :: TyFun (Max a) (Max a ~> Bool) -> Type) (a6989586621679606225 :: Max a) = TFHelper_6989586621679606220Sym1 a6989586621679606225
type Apply (TFHelper_6989586621679606200Sym0 :: TyFun (Min a) (Min a ~> Bool) -> Type) (a6989586621679606205 :: Min a) 
Instance details

Defined in Data.Semigroup.Singletons.Internal

type Apply (TFHelper_6989586621679606200Sym0 :: TyFun (Min a) (Min a ~> Bool) -> Type) (a6989586621679606205 :: Min a) = TFHelper_6989586621679606200Sym1 a6989586621679606205
type Apply (TFHelper_6989586621679606280Sym0 :: TyFun (WrappedMonoid m) (WrappedMonoid m ~> Bool) -> Type) (a6989586621679606285 :: WrappedMonoid m) 
Instance details

Defined in Data.Semigroup.Singletons.Internal

type Apply (TFHelper_6989586621679606280Sym0 :: TyFun (WrappedMonoid m) (WrappedMonoid m ~> Bool) -> Type) (a6989586621679606285 :: WrappedMonoid m) = TFHelper_6989586621679606280Sym1 a6989586621679606285
type Apply (TFHelper_6989586621679606106Sym0 :: TyFun (Dual a) (Dual a ~> Bool) -> Type) (a6989586621679606111 :: Dual a) 
Instance details

Defined in Data.Semigroup.Singletons.Internal

type Apply (TFHelper_6989586621679606106Sym0 :: TyFun (Dual a) (Dual a ~> Bool) -> Type) (a6989586621679606111 :: Dual a) = TFHelper_6989586621679606106Sym1 a6989586621679606111
type Apply (TFHelper_6989586621679606180Sym0 :: TyFun (Product a) (Product a ~> Bool) -> Type) (a6989586621679606185 :: Product a) 
Instance details

Defined in Data.Semigroup.Singletons.Internal

type Apply (TFHelper_6989586621679606180Sym0 :: TyFun (Product a) (Product a ~> Bool) -> Type) (a6989586621679606185 :: Product a) = TFHelper_6989586621679606180Sym1 a6989586621679606185
type Apply (TFHelper_6989586621679606160Sym0 :: TyFun (Sum a) (Sum a ~> Bool) -> Type) (a6989586621679606165 :: Sum a) 
Instance details

Defined in Data.Semigroup.Singletons.Internal

type Apply (TFHelper_6989586621679606160Sym0 :: TyFun (Sum a) (Sum a ~> Bool) -> Type) (a6989586621679606165 :: Sum a) = TFHelper_6989586621679606160Sym1 a6989586621679606165
type Apply (TFHelper_6989586621679130622Sym0 :: TyFun (NonEmpty a) (NonEmpty a ~> Bool) -> Type) (a6989586621679130627 :: NonEmpty a) 
Instance details

Defined in Data.Eq.Singletons

type Apply (TFHelper_6989586621679130622Sym0 :: TyFun (NonEmpty a) (NonEmpty a ~> Bool) -> Type) (a6989586621679130627 :: NonEmpty a) = TFHelper_6989586621679130622Sym1 a6989586621679130627
type Apply (TFHelper_6989586621679130516Sym0 :: TyFun (Maybe a) (Maybe a ~> Bool) -> Type) (a6989586621679130521 :: Maybe a) 
Instance details

Defined in Data.Eq.Singletons

type Apply (TFHelper_6989586621679130516Sym0 :: TyFun (Maybe a) (Maybe a ~> Bool) -> Type) (a6989586621679130521 :: Maybe a) = TFHelper_6989586621679130516Sym1 a6989586621679130521
type Apply (TFHelper_6989586621679130547Sym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679130552 :: [a]) 
Instance details

Defined in Data.Eq.Singletons

type Apply (TFHelper_6989586621679130547Sym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679130552 :: [a]) = TFHelper_6989586621679130547Sym1 a6989586621679130552
type Apply (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679731830 :: [a]) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679731830 :: [a]) = IsInfixOfSym1 a6989586621679731830
type Apply (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679731844 :: [a]) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679731844 :: [a]) = IsPrefixOfSym1 a6989586621679731844
type Apply (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679731837 :: [a]) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679731837 :: [a]) = IsSuffixOfSym1 a6989586621679731837
type Apply (ListisPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621680002140 :: [a]) 
Instance details

Defined in Data.List.Singletons.Internal.Disambiguation

type Apply (ListisPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621680002140 :: [a]) = ListisPrefixOfSym1 a6989586621680002140
type Apply (Let6989586621679731363Scrutinee_6989586621679727542Sym1 x6989586621679731361 :: TyFun [a] (TyFun (k1 ~> Bool) (TyFun k Bool -> Type) -> Type) -> Type) (xs6989586621679731362 :: [a]) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Let6989586621679731363Scrutinee_6989586621679727542Sym1 x6989586621679731361 :: TyFun [a] (TyFun (k1 ~> Bool) (TyFun k Bool -> Type) -> Type) -> Type) (xs6989586621679731362 :: [a]) = Let6989586621679731363Scrutinee_6989586621679727542Sym2 x6989586621679731361 xs6989586621679731362 :: TyFun (k1 ~> Bool) (TyFun k Bool -> Type) -> Type
type Apply (Let6989586621679731071Scrutinee_6989586621679727570Sym2 y6989586621679731068 ys6989586621679731069 :: TyFun [k1] (TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type) -> Type) (xs6989586621679731070 :: [k1]) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Let6989586621679731071Scrutinee_6989586621679727570Sym2 y6989586621679731068 ys6989586621679731069 :: TyFun [k1] (TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type) -> Type) (xs6989586621679731070 :: [k1]) = Let6989586621679731071Scrutinee_6989586621679727570Sym3 y6989586621679731068 ys6989586621679731069 xs6989586621679731070 :: TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type
type Apply (Let6989586621679731087Scrutinee_6989586621679727568Sym2 x6989586621679731084 xs6989586621679731085 :: TyFun [k1] (TyFun k3 Bool -> Type) -> Type) (ls6989586621679731086 :: [k1]) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Let6989586621679731087Scrutinee_6989586621679727568Sym2 x6989586621679731084 xs6989586621679731085 :: TyFun [k1] (TyFun k3 Bool -> Type) -> Type) (ls6989586621679731086 :: [k1]) = Let6989586621679731087Scrutinee_6989586621679727568Sym3 x6989586621679731084 xs6989586621679731085 ls6989586621679731086 :: TyFun k3 Bool -> Type
type Apply (IsLeftSym0 :: TyFun (Either a b) Bool -> Type) (a6989586621679277095 :: Either a b) 
Instance details

Defined in Data.Either.Singletons

type Apply (IsLeftSym0 :: TyFun (Either a b) Bool -> Type) (a6989586621679277095 :: Either a b) = IsLeft a6989586621679277095
type Apply (IsRightSym0 :: TyFun (Either a b) Bool -> Type) (a6989586621679277092 :: Either a b) 
Instance details

Defined in Data.Either.Singletons

type Apply (IsRightSym0 :: TyFun (Either a b) Bool -> Type) (a6989586621679277092 :: Either a b) = IsRight a6989586621679277092
type Apply (Null_6989586621680194155Sym0 :: TyFun (Either a1 a2) Bool -> Type) (a6989586621680194161 :: Either a1 a2) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Null_6989586621680194155Sym0 :: TyFun (Either a1 a2) Bool -> Type) (a6989586621680194161 :: Either a1 a2) = Null_6989586621680194155 a6989586621680194161
type Apply (Elem_6989586621680194236Sym1 a6989586621680194241 :: TyFun (Proxy a) Bool -> Type) (a6989586621680194242 :: Proxy a) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Elem_6989586621680194236Sym1 a6989586621680194241 :: TyFun (Proxy a) Bool -> Type) (a6989586621680194242 :: Proxy a) = Elem_6989586621680194236 a6989586621680194241 a6989586621680194242
type Apply (Null_6989586621680194229Sym0 :: TyFun (Proxy a) Bool -> Type) (a6989586621680194233 :: Proxy a) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Null_6989586621680194229Sym0 :: TyFun (Proxy a) Bool -> Type) (a6989586621680194233 :: Proxy a) = Null_6989586621680194229 a6989586621680194233
type Apply (TFHelper_6989586621679130594Sym1 a6989586621679130599 :: TyFun (Either a b) Bool -> Type) (a6989586621679130600 :: Either a b) 
Instance details

Defined in Data.Eq.Singletons

type Apply (TFHelper_6989586621679130594Sym1 a6989586621679130599 :: TyFun (Either a b) Bool -> Type) (a6989586621679130600 :: Either a b) = TFHelper_6989586621679130594 a6989586621679130599 a6989586621679130600
type Apply (TFHelper_6989586621680163384Sym1 a6989586621680163389 :: TyFun (Proxy s) Bool -> Type) (a6989586621680163390 :: Proxy s) 
Instance details

Defined in Data.Proxy.Singletons

type Apply (TFHelper_6989586621680163384Sym1 a6989586621680163389 :: TyFun (Proxy s) Bool -> Type) (a6989586621680163390 :: Proxy s) = TFHelper_6989586621680163384 a6989586621680163389 a6989586621680163390
type Apply (TFHelper_6989586621680605296Sym1 a6989586621680605301 :: TyFun (Arg a b) Bool -> Type) (a6989586621680605302 :: Arg a b) 
Instance details

Defined in Data.Semigroup.Singletons

type Apply (TFHelper_6989586621680605296Sym1 a6989586621680605301 :: TyFun (Arg a b) Bool -> Type) (a6989586621680605302 :: Arg a b) = TFHelper_6989586621680605296 a6989586621680605301 a6989586621680605302
type Apply (TFHelper_6989586621679130662Sym1 a6989586621679130667 :: TyFun (a, b) Bool -> Type) (a6989586621679130668 :: (a, b)) 
Instance details

Defined in Data.Eq.Singletons

type Apply (TFHelper_6989586621679130662Sym1 a6989586621679130667 :: TyFun (a, b) Bool -> Type) (a6989586621679130668 :: (a, b)) = TFHelper_6989586621679130662 a6989586621679130667 a6989586621679130668
type Apply (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679731576 :: a ~> (a ~> Bool)) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679731576 :: a ~> (a ~> Bool)) = DeleteFirstsBySym1 a6989586621679731576
type Apply (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679731401 :: a ~> (a ~> Bool)) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679731401 :: a ~> (a ~> Bool)) = IntersectBySym1 a6989586621679731401
type Apply (UnionBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679731040 :: a ~> (a ~> Bool)) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (UnionBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679731040 :: a ~> (a ~> Bool)) = UnionBySym1 a6989586621679731040
type Apply (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) (a6989586621679731193 :: a ~> (a ~> Bool)) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) (a6989586621679731193 :: a ~> (a ~> Bool)) = GroupBySym1 a6989586621679731193
type Apply (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) (a6989586621679731060 :: a ~> (a ~> Bool)) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) (a6989586621679731060 :: a ~> (a ~> Bool)) = NubBySym1 a6989586621679731060
type Apply (ListnubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) (a6989586621680002102 :: a ~> (a ~> Bool)) 
Instance details

Defined in Data.List.Singletons.Internal.Disambiguation

type Apply (ListnubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) (a6989586621680002102 :: a ~> (a ~> Bool)) = ListnubBySym1 a6989586621680002102
type Apply (Elem_bySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> Bool)) -> Type) (a6989586621679731050 :: a ~> (a ~> Bool)) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Elem_bySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> Bool)) -> Type) (a6989586621679731050 :: a ~> (a ~> Bool)) = Elem_bySym1 a6989586621679731050
type Apply (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) (a6989586621679731586 :: a ~> (a ~> Bool)) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) (a6989586621679731586 :: a ~> (a ~> Bool)) = DeleteBySym1 a6989586621679731586
type Apply (UntilSym0 :: TyFun (a ~> Bool) ((a ~> a) ~> (a ~> a)) -> Type) (a6989586621679248366 :: a ~> Bool) 
Instance details

Defined in GHC.Base.Singletons

type Apply (UntilSym0 :: TyFun (a ~> Bool) ((a ~> a) ~> (a ~> a)) -> Type) (a6989586621679248366 :: a ~> Bool) = UntilSym1 a6989586621679248366
type Apply (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Nat) -> Type) (a6989586621679731453 :: a ~> Bool) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Nat) -> Type) (a6989586621679731453 :: a ~> Bool) = FindIndexSym1 a6989586621679731453
type Apply (FindSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe a) -> Type) (a6989586621679731480 :: a ~> Bool) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (FindSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe a) -> Type) (a6989586621679731480 :: a ~> Bool) = FindSym1 a6989586621679731480
type Apply (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679731283 :: a ~> Bool) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679731283 :: a ~> Bool) = BreakSym1 a6989586621679731283
type Apply (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679731171 :: a ~> Bool) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679731171 :: a ~> Bool) = PartitionSym1 a6989586621679731171
type Apply (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679731318 :: a ~> Bool) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679731318 :: a ~> Bool) = SpanSym1 a6989586621679731318
type Apply (ListpartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621680002162 :: a ~> Bool) 
Instance details

Defined in Data.List.Singletons.Internal.Disambiguation

type Apply (ListpartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621680002162 :: a ~> Bool) = ListpartitionSym1 a6989586621680002162
type Apply (ListspanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621680002184 :: a ~> Bool) 
Instance details

Defined in Data.List.Singletons.Internal.Disambiguation

type Apply (ListspanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621680002184 :: a ~> Bool) = ListspanSym1 a6989586621680002184
type Apply (AllSym0 :: TyFun (a ~> Bool) ([a] ~> Bool) -> Type) (a6989586621679732047 :: a ~> Bool) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (AllSym0 :: TyFun (a ~> Bool) ([a] ~> Bool) -> Type) (a6989586621679732047 :: a ~> Bool) = AllSym1 a6989586621679732047
type Apply (AnySym0 :: TyFun (a ~> Bool) ([a] ~> Bool) -> Type) (a6989586621679732039 :: a ~> Bool) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (AnySym0 :: TyFun (a ~> Bool) ([a] ~> Bool) -> Type) (a6989586621679732039 :: a ~> Bool) = AnySym1 a6989586621679732039
type Apply (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Nat]) -> Type) (a6989586621679731430 :: a ~> Bool) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Nat]) -> Type) (a6989586621679731430 :: a ~> Bool) = FindIndicesSym1 a6989586621679731430
type Apply (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679731355 :: a ~> Bool) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679731355 :: a ~> Bool) = DropWhileEndSym1 a6989586621679731355
type Apply (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679731372 :: a ~> Bool) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679731372 :: a ~> Bool) = DropWhileSym1 a6989586621679731372
type Apply (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679731487 :: a ~> Bool) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679731487 :: a ~> Bool) = FilterSym1 a6989586621679731487
type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679731387 :: a ~> Bool) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679731387 :: a ~> Bool) = TakeWhileSym1 a6989586621679731387
type Apply (ListdropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621680002195 :: a ~> Bool) 
Instance details

Defined in Data.List.Singletons.Internal.Disambiguation

type Apply (ListdropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621680002195 :: a ~> Bool) = ListdropWhileSym1 a6989586621680002195
type Apply (ListfilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621680002173 :: a ~> Bool) 
Instance details

Defined in Data.List.Singletons.Internal.Disambiguation

type Apply (ListfilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621680002173 :: a ~> Bool) = ListfilterSym1 a6989586621680002173
type Apply (ListtakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621680002206 :: a ~> Bool) 
Instance details

Defined in Data.List.Singletons.Internal.Disambiguation

type Apply (ListtakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621680002206 :: a ~> Bool) = ListtakeWhileSym1 a6989586621680002206
type Apply (SelectSym0 :: TyFun (a ~> Bool) (a ~> (([a], [a]) ~> ([a], [a]))) -> Type) (a6989586621679731156 :: a ~> Bool) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (SelectSym0 :: TyFun (a ~> Bool) (a ~> (([a], [a]) ~> ([a], [a]))) -> Type) (a6989586621679731156 :: a ~> Bool) = SelectSym1 a6989586621679731156
type Apply (Let6989586621679731296X_6989586621679731297Sym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] ([k], [k]) -> Type) -> Type) -> Type) (p6989586621679731287 :: k ~> Bool) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Let6989586621679731296X_6989586621679731297Sym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] ([k], [k]) -> Type) -> Type) -> Type) (p6989586621679731287 :: k ~> Bool) = Let6989586621679731296X_6989586621679731297Sym1 p6989586621679731287
type Apply (Let6989586621679731331X_6989586621679731332Sym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] ([k], [k]) -> Type) -> Type) -> Type) (p6989586621679731322 :: k ~> Bool) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Let6989586621679731331X_6989586621679731332Sym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] ([k], [k]) -> Type) -> Type) -> Type) (p6989586621679731322 :: k ~> Bool) = Let6989586621679731331X_6989586621679731332Sym1 p6989586621679731322
type Apply (Let6989586621679731296YsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621679731287 :: k ~> Bool) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Let6989586621679731296YsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621679731287 :: k ~> Bool) = Let6989586621679731296YsSym1 p6989586621679731287
type Apply (Let6989586621679731296ZsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621679731287 :: k ~> Bool) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Let6989586621679731296ZsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621679731287 :: k ~> Bool) = Let6989586621679731296ZsSym1 p6989586621679731287
type Apply (Let6989586621679731331YsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621679731322 :: k ~> Bool) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Let6989586621679731331YsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621679731322 :: k ~> Bool) = Let6989586621679731331YsSym1 p6989586621679731322
type Apply (Let6989586621679731331ZsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621679731322 :: k ~> Bool) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Let6989586621679731331ZsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621679731322 :: k ~> Bool) = Let6989586621679731331ZsSym1 p6989586621679731322
type Apply (TFHelper_6989586621679130594Sym0 :: TyFun (Either a b) (Either a b ~> Bool) -> Type) (a6989586621679130599 :: Either a b) 
Instance details

Defined in Data.Eq.Singletons

type Apply (TFHelper_6989586621679130594Sym0 :: TyFun (Either a b) (Either a b ~> Bool) -> Type) (a6989586621679130599 :: Either a b) = TFHelper_6989586621679130594Sym1 a6989586621679130599
type Apply (TFHelper_6989586621680163384Sym0 :: TyFun (Proxy s) (Proxy s ~> Bool) -> Type) (a6989586621680163389 :: Proxy s) 
Instance details

Defined in Data.Proxy.Singletons

type Apply (TFHelper_6989586621680163384Sym0 :: TyFun (Proxy s) (Proxy s ~> Bool) -> Type) (a6989586621680163389 :: Proxy s) = TFHelper_6989586621680163384Sym1 a6989586621680163389
type Apply (TFHelper_6989586621680605296Sym0 :: TyFun (Arg a b) (Arg a b ~> Bool) -> Type) (a6989586621680605301 :: Arg a b) 
Instance details

Defined in Data.Semigroup.Singletons

type Apply (TFHelper_6989586621680605296Sym0 :: TyFun (Arg a b) (Arg a b ~> Bool) -> Type) (a6989586621680605301 :: Arg a b) = TFHelper_6989586621680605296Sym1 a6989586621680605301
type Apply (MfilterSym0 :: TyFun (a ~> Bool) (m a ~> m a) -> Type) (a6989586621680892560 :: a ~> Bool) 
Instance details

Defined in Control.Monad.Singletons

type Apply (MfilterSym0 :: TyFun (a ~> Bool) (m a ~> m a) -> Type) (a6989586621680892560 :: a ~> Bool) = MfilterSym1 a6989586621680892560 :: TyFun (m a) (m a) -> Type
type Apply (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) (a6989586621680193279 :: a ~> Bool) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) (a6989586621680193279 :: a ~> Bool) = FindSym1 a6989586621680193279 :: TyFun (t a) (Maybe a) -> Type
type Apply (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621680193346 :: a ~> Bool) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621680193346 :: a ~> Bool) = AllSym1 a6989586621680193346 :: TyFun (t a) Bool -> Type
type Apply (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621680193355 :: a ~> Bool) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621680193355 :: a ~> Bool) = AnySym1 a6989586621680193355 :: TyFun (t a) Bool -> Type
type Apply (Lambda_6989586621680193283Sym0 :: TyFun (a ~> Bool) (TyFun k (TyFun a (First a) -> Type) -> Type) -> Type) (p6989586621680193281 :: a ~> Bool) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Lambda_6989586621680193283Sym0 :: TyFun (a ~> Bool) (TyFun k (TyFun a (First a) -> Type) -> Type) -> Type) (p6989586621680193281 :: a ~> Bool) = Lambda_6989586621680193283Sym1 p6989586621680193281 :: TyFun k (TyFun a (First a) -> Type) -> Type
type Apply (Lambda_6989586621679731359Sym0 :: TyFun (a ~> Bool) (TyFun k (TyFun a (TyFun [a] [a] -> Type) -> Type) -> Type) -> Type) (p6989586621679731357 :: a ~> Bool) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Lambda_6989586621679731359Sym0 :: TyFun (a ~> Bool) (TyFun k (TyFun a (TyFun [a] [a] -> Type) -> Type) -> Type) -> Type) (p6989586621679731357 :: a ~> Bool) = Lambda_6989586621679731359Sym1 p6989586621679731357 :: TyFun k (TyFun a (TyFun [a] [a] -> Type) -> Type) -> Type
type Apply (FilterMSym0 :: TyFun (a ~> m Bool) ([a] ~> m [a]) -> Type) (a6989586621680892722 :: a ~> m Bool) 
Instance details

Defined in Control.Monad.Singletons

type Apply (FilterMSym0 :: TyFun (a ~> m Bool) ([a] ~> m [a]) -> Type) (a6989586621680892722 :: a ~> m Bool) = FilterMSym1 a6989586621680892722
type Apply (Let6989586621679731198X_6989586621679731199Sym0 :: TyFun (k1 ~> (a ~> Bool)) (TyFun k1 (TyFun [a] ([a], [a]) -> Type) -> Type) -> Type) (eq6989586621679731195 :: k1 ~> (a ~> Bool)) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Let6989586621679731198X_6989586621679731199Sym0 :: TyFun (k1 ~> (a ~> Bool)) (TyFun k1 (TyFun [a] ([a], [a]) -> Type) -> Type) -> Type) (eq6989586621679731195 :: k1 ~> (a ~> Bool)) = Let6989586621679731198X_6989586621679731199Sym1 eq6989586621679731195
type Apply (Let6989586621679731198YsSym0 :: TyFun (k1 ~> (a ~> Bool)) (TyFun k1 (TyFun [a] [a] -> Type) -> Type) -> Type) (eq6989586621679731195 :: k1 ~> (a ~> Bool)) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Let6989586621679731198YsSym0 :: TyFun (k1 ~> (a ~> Bool)) (TyFun k1 (TyFun [a] [a] -> Type) -> Type) -> Type) (eq6989586621679731195 :: k1 ~> (a ~> Bool)) = Let6989586621679731198YsSym1 eq6989586621679731195
type Apply (Let6989586621679731198ZsSym0 :: TyFun (k1 ~> (a ~> Bool)) (TyFun k1 (TyFun [a] [a] -> Type) -> Type) -> Type) (eq6989586621679731195 :: k1 ~> (a ~> Bool)) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Let6989586621679731198ZsSym0 :: TyFun (k1 ~> (a ~> Bool)) (TyFun k1 (TyFun [a] [a] -> Type) -> Type) -> Type) (eq6989586621679731195 :: k1 ~> (a ~> Bool)) = Let6989586621679731198ZsSym1 eq6989586621679731195
type Apply (Let6989586621679731064NubBy'Sym0 :: TyFun (k1 ~> (k1 ~> Bool)) (TyFun k (TyFun [k1] ([k1] ~> [k1]) -> Type) -> Type) -> Type) (eq6989586621679731062 :: k1 ~> (k1 ~> Bool)) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Let6989586621679731064NubBy'Sym0 :: TyFun (k1 ~> (k1 ~> Bool)) (TyFun k (TyFun [k1] ([k1] ~> [k1]) -> Type) -> Type) -> Type) (eq6989586621679731062 :: k1 ~> (k1 ~> Bool)) = Let6989586621679731064NubBy'Sym1 eq6989586621679731062 :: TyFun k (TyFun [k1] ([k1] ~> [k1]) -> Type) -> Type
type Apply (Let6989586621679248372GoSym0 :: TyFun (k1 ~> Bool) (TyFun (k1 ~> k1) (TyFun k2 (TyFun k1 k1 -> Type) -> Type) -> Type) -> Type) (p6989586621679248369 :: k1 ~> Bool) 
Instance details

Defined in GHC.Base.Singletons

type Apply (Let6989586621679248372GoSym0 :: TyFun (k1 ~> Bool) (TyFun (k1 ~> k1) (TyFun k2 (TyFun k1 k1 -> Type) -> Type) -> Type) -> Type) (p6989586621679248369 :: k1 ~> Bool) = Let6989586621679248372GoSym1 p6989586621679248369 :: TyFun (k1 ~> k1) (TyFun k2 (TyFun k1 k1 -> Type) -> Type) -> Type
type Apply (TFHelper_6989586621679130662Sym0 :: TyFun (a, b) ((a, b) ~> Bool) -> Type) (a6989586621679130667 :: (a, b)) 
Instance details

Defined in Data.Eq.Singletons

type Apply (TFHelper_6989586621679130662Sym0 :: TyFun (a, b) ((a, b) ~> Bool) -> Type) (a6989586621679130667 :: (a, b)) = TFHelper_6989586621679130662Sym1 a6989586621679130667
type Apply (Lambda_6989586621680892564Sym0 :: TyFun (k1 ~> Bool) (TyFun k (TyFun k1 (m k1) -> Type) -> Type) -> Type) (p6989586621680892562 :: k1 ~> Bool) 
Instance details

Defined in Control.Monad.Singletons

type Apply (Lambda_6989586621680892564Sym0 :: TyFun (k1 ~> Bool) (TyFun k (TyFun k1 (m k1) -> Type) -> Type) -> Type) (p6989586621680892562 :: k1 ~> Bool) = Lambda_6989586621680892564Sym1 p6989586621680892562 :: TyFun k (TyFun k1 (m k1) -> Type) -> Type
type Apply (Lambda_6989586621680892726Sym0 :: TyFun (k2 ~> f Bool) (TyFun k3 (TyFun k2 (f [k2] ~> f [k2]) -> Type) -> Type) -> Type) (p6989586621680892724 :: k2 ~> f Bool) 
Instance details

Defined in Control.Monad.Singletons

type Apply (Lambda_6989586621680892726Sym0 :: TyFun (k2 ~> f Bool) (TyFun k3 (TyFun k2 (f [k2] ~> f [k2]) -> Type) -> Type) -> Type) (p6989586621680892724 :: k2 ~> f Bool) = Lambda_6989586621680892726Sym1 p6989586621680892724 :: TyFun k3 (TyFun k2 (f [k2] ~> f [k2]) -> Type) -> Type
type Apply (Lambda_6989586621679731412Sym0 :: TyFun (b ~> (a ~> Bool)) (TyFun k1 (TyFun k2 (TyFun a (TyFun [a] (TyFun b (m b) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (eq6989586621679731404 :: b ~> (a ~> Bool)) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Lambda_6989586621679731412Sym0 :: TyFun (b ~> (a ~> Bool)) (TyFun k1 (TyFun k2 (TyFun a (TyFun [a] (TyFun b (m b) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (eq6989586621679731404 :: b ~> (a ~> Bool)) = Lambda_6989586621679731412Sym1 eq6989586621679731404 :: TyFun k1 (TyFun k2 (TyFun a (TyFun [a] (TyFun b (m b) -> Type) -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679731363Scrutinee_6989586621679727542Sym2 x6989586621679731361 xs6989586621679731362 :: TyFun (k1 ~> Bool) (TyFun k Bool -> Type) -> Type) (p6989586621679731357 :: k1 ~> Bool) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Let6989586621679731363Scrutinee_6989586621679727542Sym2 x6989586621679731361 xs6989586621679731362 :: TyFun (k1 ~> Bool) (TyFun k Bool -> Type) -> Type) (p6989586621679731357 :: k1 ~> Bool) = Let6989586621679731363Scrutinee_6989586621679727542Sym3 x6989586621679731361 xs6989586621679731362 p6989586621679731357 :: TyFun k Bool -> Type
type Apply (Let6989586621679731071Scrutinee_6989586621679727570Sym3 y6989586621679731068 ys6989586621679731069 xs6989586621679731070 :: TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type) (eq6989586621679731062 :: k1 ~> (k1 ~> Bool)) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Let6989586621679731071Scrutinee_6989586621679727570Sym3 y6989586621679731068 ys6989586621679731069 xs6989586621679731070 :: TyFun (k1 ~> (k1 ~> Bool)) (TyFun k3 Bool -> Type) -> Type) (eq6989586621679731062 :: k1 ~> (k1 ~> Bool)) = Let6989586621679731071Scrutinee_6989586621679727570Sym4 y6989586621679731068 ys6989586621679731069 xs6989586621679731070 eq6989586621679731062 :: TyFun k3 Bool -> Type
type Apply (TFHelper_6989586621680428549Sym1 a6989586621680428554 :: TyFun (Const a b) Bool -> Type) (a6989586621680428555 :: Const a b) 
Instance details

Defined in Data.Functor.Const.Singletons

type Apply (TFHelper_6989586621680428549Sym1 a6989586621680428554 :: TyFun (Const a b) Bool -> Type) (a6989586621680428555 :: Const a b) = TFHelper_6989586621680428549 a6989586621680428554 a6989586621680428555
type Apply (TFHelper_6989586621679130700Sym1 a6989586621679130705 :: TyFun (a, b, c) Bool -> Type) (a6989586621679130706 :: (a, b, c)) 
Instance details

Defined in Data.Eq.Singletons

type Apply (TFHelper_6989586621679130700Sym1 a6989586621679130705 :: TyFun (a, b, c) Bool -> Type) (a6989586621679130706 :: (a, b, c)) = TFHelper_6989586621679130700 a6989586621679130705 a6989586621679130706
type Apply (TFHelper_6989586621680428549Sym0 :: TyFun (Const a b) (Const a b ~> Bool) -> Type) (a6989586621680428554 :: Const a b) 
Instance details

Defined in Data.Functor.Const.Singletons

type Apply (TFHelper_6989586621680428549Sym0 :: TyFun (Const a b) (Const a b ~> Bool) -> Type) (a6989586621680428554 :: Const a b) = TFHelper_6989586621680428549Sym1 a6989586621680428554
type Apply (TFHelper_6989586621679130700Sym0 :: TyFun (a, b, c) ((a, b, c) ~> Bool) -> Type) (a6989586621679130705 :: (a, b, c)) 
Instance details

Defined in Data.Eq.Singletons

type Apply (TFHelper_6989586621679130700Sym0 :: TyFun (a, b, c) ((a, b, c) ~> Bool) -> Type) (a6989586621679130705 :: (a, b, c)) = TFHelper_6989586621679130700Sym1 a6989586621679130705
type Apply (TFHelper_6989586621679130749Sym1 a6989586621679130754 :: TyFun (a, b, c, d) Bool -> Type) (a6989586621679130755 :: (a, b, c, d)) 
Instance details

Defined in Data.Eq.Singletons

type Apply (TFHelper_6989586621679130749Sym1 a6989586621679130754 :: TyFun (a, b, c, d) Bool -> Type) (a6989586621679130755 :: (a, b, c, d)) = TFHelper_6989586621679130749 a6989586621679130754 a6989586621679130755
type Apply (TFHelper_6989586621679130749Sym0 :: TyFun (a, b, c, d) ((a, b, c, d) ~> Bool) -> Type) (a6989586621679130754 :: (a, b, c, d)) 
Instance details

Defined in Data.Eq.Singletons

type Apply (TFHelper_6989586621679130749Sym0 :: TyFun (a, b, c, d) ((a, b, c, d) ~> Bool) -> Type) (a6989586621679130754 :: (a, b, c, d)) = TFHelper_6989586621679130749Sym1 a6989586621679130754
type Apply (TFHelper_6989586621679130809Sym1 a6989586621679130814 :: TyFun (a, b, c, d, e) Bool -> Type) (a6989586621679130815 :: (a, b, c, d, e)) 
Instance details

Defined in Data.Eq.Singletons

type Apply (TFHelper_6989586621679130809Sym1 a6989586621679130814 :: TyFun (a, b, c, d, e) Bool -> Type) (a6989586621679130815 :: (a, b, c, d, e)) = TFHelper_6989586621679130809 a6989586621679130814 a6989586621679130815
type Apply (TFHelper_6989586621679130809Sym0 :: TyFun (a, b, c, d, e) ((a, b, c, d, e) ~> Bool) -> Type) (a6989586621679130814 :: (a, b, c, d, e)) 
Instance details

Defined in Data.Eq.Singletons

type Apply (TFHelper_6989586621679130809Sym0 :: TyFun (a, b, c, d, e) ((a, b, c, d, e) ~> Bool) -> Type) (a6989586621679130814 :: (a, b, c, d, e)) = TFHelper_6989586621679130809Sym1 a6989586621679130814
type Apply (TFHelper_6989586621679130880Sym1 a6989586621679130885 :: TyFun (a, b, c, d, e, f) Bool -> Type) (a6989586621679130886 :: (a, b, c, d, e, f)) 
Instance details

Defined in Data.Eq.Singletons

type Apply (TFHelper_6989586621679130880Sym1 a6989586621679130885 :: TyFun (a, b, c, d, e, f) Bool -> Type) (a6989586621679130886 :: (a, b, c, d, e, f)) = TFHelper_6989586621679130880 a6989586621679130885 a6989586621679130886
type Apply (TFHelper_6989586621679130880Sym0 :: TyFun (a, b, c, d, e, f) ((a, b, c, d, e, f) ~> Bool) -> Type) (a6989586621679130885 :: (a, b, c, d, e, f)) 
Instance details

Defined in Data.Eq.Singletons

type Apply (TFHelper_6989586621679130880Sym0 :: TyFun (a, b, c, d, e, f) ((a, b, c, d, e, f) ~> Bool) -> Type) (a6989586621679130885 :: (a, b, c, d, e, f)) = TFHelper_6989586621679130880Sym1 a6989586621679130885
type Apply (TFHelper_6989586621679130962Sym1 a6989586621679130967 :: TyFun (a, b, c, d, e, f, g) Bool -> Type) (a6989586621679130968 :: (a, b, c, d, e, f, g)) 
Instance details

Defined in Data.Eq.Singletons

type Apply (TFHelper_6989586621679130962Sym1 a6989586621679130967 :: TyFun (a, b, c, d, e, f, g) Bool -> Type) (a6989586621679130968 :: (a, b, c, d, e, f, g)) = TFHelper_6989586621679130962 a6989586621679130967 a6989586621679130968
type Apply (TFHelper_6989586621679130962Sym0 :: TyFun (a, b, c, d, e, f, g) ((a, b, c, d, e, f, g) ~> Bool) -> Type) (a6989586621679130967 :: (a, b, c, d, e, f, g)) 
Instance details

Defined in Data.Eq.Singletons

type Apply (TFHelper_6989586621679130962Sym0 :: TyFun (a, b, c, d, e, f, g) ((a, b, c, d, e, f, g) ~> Bool) -> Type) (a6989586621679130967 :: (a, b, c, d, e, f, g)) = TFHelper_6989586621679130962Sym1 a6989586621679130967

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

Defined in Distribution.Utils.Structured

Chunk ByteString 
Instance details

Defined in Data.Attoparsec.Internal.Types

Associated Types

type ChunkElem ByteString #

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 #

IsString ByteString

Beware: fromString truncates multi-byte characters to octets. e.g. "枯朶に烏のとまりけり秋の暮" becomes �6k�nh~�Q��n�

Instance details

Defined in Data.ByteString.Internal

Monoid ByteString 
Instance details

Defined in Data.ByteString.Internal

Semigroup ByteString 
Instance details

Defined in Data.ByteString.Internal

IsList ByteString

Since: bytestring-0.10.12.0

Instance details

Defined in Data.ByteString.Internal

Associated Types

type Item ByteString #

Read ByteString 
Instance details

Defined in Data.ByteString.Internal

Show ByteString 
Instance details

Defined in Data.ByteString.Internal

NFData ByteString 
Instance details

Defined in Data.ByteString.Internal

Methods

rnf :: ByteString -> () #

FromBuilder ByteString 
Instance details

Defined in Fmt.Internal.Core

Eq ByteString 
Instance details

Defined in Data.ByteString.Internal

Ord ByteString 
Instance details

Defined in Data.ByteString.Internal

Hashable ByteString 
Instance details

Defined in Data.Hashable.Class

Ixed ByteString 
Instance details

Defined in Control.Lens.At

HasAnnotation ByteString Source # 
Instance details

Defined in Lorentz.Annotation

BytesLike ByteString Source # 
Instance details

Defined in Lorentz.Bytes

ConcatOpHs ByteString Source # 
Instance details

Defined in Lorentz.Polymorphic

SizeOpHs ByteString Source # 
Instance details

Defined in Lorentz.Polymorphic

SliceOpHs ByteString Source # 
Instance details

Defined in Lorentz.Polymorphic

Stream ByteString 
Instance details

Defined in Text.Megaparsec.Stream

Associated Types

type Token ByteString #

type Tokens ByteString #

TraversableStream ByteString 
Instance details

Defined in Text.Megaparsec.Stream

VisualStream ByteString 
Instance details

Defined in Text.Megaparsec.Stream

HasRPCRepr ByteString 
Instance details

Defined in Morley.AsRPC

Associated Types

type AsRPC ByteString

TypeHasDoc ByteString 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions ByteString :: FieldDescriptions #

IsoValue ByteString 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT ByteString :: T #

Container ByteString 
Instance details

Defined in Universum.Container.Class

Associated Types

type Element ByteString #

FromList ByteString 
Instance details

Defined in Universum.Container.Class

Associated Types

type ListElement ByteString #

type FromListC ByteString #

One ByteString 
Instance details

Defined in Universum.Container.Class

Associated Types

type OneItem ByteString #

Print ByteString 
Instance details

Defined in Universum.Print.Internal

Methods

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

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

ConvertUtf8 Text ByteString 
Instance details

Defined in Universum.String.Conversion

ConvertUtf8 Text ByteString 
Instance details

Defined in Universum.String.Conversion

ConvertUtf8 String ByteString 
Instance details

Defined in Universum.String.Conversion

Cons ByteString ByteString Word8 Word8 
Instance details

Defined in Control.Lens.Cons

Snoc ByteString ByteString Word8 Word8 
Instance details

Defined in Control.Lens.Cons

CanCastTo (Packed a :: Type) ByteString Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (Packed a) -> Proxy ByteString -> () Source #

CanCastTo (TSignature a :: Type) ByteString Source # 
Instance details

Defined in Lorentz.Coercions

CanCastTo (Hash alg a :: Type) ByteString Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (Hash alg a) -> Proxy ByteString -> () Source #

type ChunkElem ByteString 
Instance details

Defined in Data.Attoparsec.Internal.Types

type State ByteString 
Instance details

Defined in Data.Attoparsec.Internal.Types

type State ByteString = Buffer
type Item ByteString 
Instance details

Defined in Data.ByteString.Internal

type Index ByteString 
Instance details

Defined in Control.Lens.At

type IxValue ByteString 
Instance details

Defined in Control.Lens.At

type Token ByteString 
Instance details

Defined in Text.Megaparsec.Stream

type Tokens ByteString 
Instance details

Defined in Text.Megaparsec.Stream

type AsRPC ByteString 
Instance details

Defined in Morley.AsRPC

type AsRPC ByteString = ByteString
type TypeDocFieldDescriptions ByteString 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

type ToT ByteString 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

type ToT ByteString = 'TBytes
type PrettyShow ByteString 
Instance details

Defined in Morley.Prelude.Show

type PrettyShow ByteString = TypeError ('Text "Show instance for ByteString is not pretty") :: Constraint
type Element ByteString 
Instance details

Defined in Universum.Container.Class

type FromListC ByteString 
Instance details

Defined in Universum.Container.Class

type ListElement ByteString 
Instance details

Defined in Universum.Container.Class

type OneItem ByteString 
Instance details

Defined in Universum.Container.Class

type Address = Constrained (NullConstraint :: AddressKind -> Constraint) KindedAddress #

data EpAddress #

Constructors

EpAddress' 

Bundled Patterns

pattern EpAddress :: forall (kind :: AddressKind). () => KindedAddress kind -> EpName -> EpAddress 

Instances

Instances details
Generic EpAddress 
Instance details

Defined in Morley.Michelson.Typed.Entrypoints

Associated Types

type Rep EpAddress :: Type -> Type #

Show EpAddress 
Instance details

Defined in Morley.Michelson.Typed.Entrypoints

NFData EpAddress 
Instance details

Defined in Morley.Michelson.Typed.Entrypoints

Methods

rnf :: EpAddress -> () #

Buildable EpAddress 
Instance details

Defined in Morley.Michelson.Typed.Entrypoints

Methods

build :: EpAddress -> Builder #

Eq EpAddress 
Instance details

Defined in Morley.Michelson.Typed.Entrypoints

Ord EpAddress 
Instance details

Defined in Morley.Michelson.Typed.Entrypoints

ToAddress EpAddress Source # 
Instance details

Defined in Lorentz.Address

HasAnnotation EpAddress Source # 
Instance details

Defined in Lorentz.Annotation

HasRPCRepr EpAddress 
Instance details

Defined in Morley.AsRPC

Associated Types

type AsRPC EpAddress

TypeHasDoc EpAddress 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions EpAddress :: FieldDescriptions #

IsoValue EpAddress 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT EpAddress :: T #

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 Morley.Michelson.Typed.Entrypoints

type Rep EpAddress = D1 ('MetaData "EpAddress" "Morley.Michelson.Typed.Entrypoints" "morley-1.19.0-inplace" 'False) (C1 ('MetaCons "EpAddress'" 'PrefixI 'True) (S1 ('MetaSel ('Just "eaAddress") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Address) :*: S1 ('MetaSel ('Just "eaEntrypoint") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 EpName)))
type AsRPC EpAddress 
Instance details

Defined in Morley.AsRPC

type AsRPC EpAddress = EpAddress
type TypeDocFieldDescriptions EpAddress 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

type ToT EpAddress 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

type ToT EpAddress = 'TAddress

data Mutez #

Instances

Instances details
FromJSON Mutez 
Instance details

Defined in Morley.Tezos.Core

ToJSON Mutez 
Instance details

Defined in Morley.Tezos.Core

Bounded Mutez 
Instance details

Defined in Morley.Tezos.Core

Enum Mutez 
Instance details

Defined in Morley.Tezos.Core

Generic Mutez 
Instance details

Defined in Morley.Tezos.Core

Associated Types

type Rep Mutez :: Type -> Type #

Methods

from :: Mutez -> Rep Mutez x #

to :: Rep Mutez x -> Mutez #

Show Mutez 
Instance details

Defined in Morley.Tezos.Core

Methods

showsPrec :: Int -> Mutez -> ShowS #

show :: Mutez -> String #

showList :: [Mutez] -> ShowS #

NFData Mutez 
Instance details

Defined in Morley.Tezos.Core

Methods

rnf :: Mutez -> () #

Buildable Mutez 
Instance details

Defined in Morley.Tezos.Core

Methods

build :: Mutez -> Builder #

Eq Mutez 
Instance details

Defined in Morley.Tezos.Core

Methods

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

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

Ord Mutez 
Instance details

Defined in Morley.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 #

HasAnnotation Mutez Source # 
Instance details

Defined in Lorentz.Annotation

HasRPCRepr Mutez 
Instance details

Defined in Morley.AsRPC

Associated Types

type AsRPC Mutez

TypeHasDoc Mutez 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions Mutez :: FieldDescriptions #

IsoValue Mutez 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT Mutez :: T #

HasCLReader Mutez 
Instance details

Defined in Morley.Tezos.Core

r ~ Mutez => ArithOpHs Add Mutez Mutez r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Mutez ': (Mutez ': s)) :-> (r ': s) Source #

r ~ Maybe (Natural, Mutez) => ArithOpHs EDiv Mutez Mutez r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Mutez ': (Mutez ': s)) :-> (r ': s) Source #

r ~ Maybe (Mutez, Mutez) => ArithOpHs EDiv Mutez Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Mutez ': (Natural ': s)) :-> (r ': s) Source #

r ~ Mutez => ArithOpHs Mul Mutez Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Mutez ': (Natural ': s)) :-> (r ': s) Source #

r ~ Mutez => ArithOpHs Mul Natural Mutez r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Mutez ': s)) :-> (r ': s) Source #

type Rep Mutez 
Instance details

Defined in Morley.Tezos.Core

type Rep Mutez = D1 ('MetaData "Mutez" "Morley.Tezos.Core" "morley-1.19.0-inplace" 'True) (C1 ('MetaCons "UnsafeMutez" 'PrefixI 'True) (S1 ('MetaSel ('Just "unMutez") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word63)))
type AsRPC Mutez 
Instance details

Defined in Morley.AsRPC

type AsRPC Mutez = Mutez
type TypeDocFieldDescriptions Mutez 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

type ToT Mutez 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

type ToT Mutez = 'TMutez

data Never Source #

Instances

Instances details
Generic Never Source # 
Instance details

Defined in Lorentz.Value

Associated Types

type Rep Never :: Type -> Type #

Methods

from :: Never -> Rep Never x #

to :: Rep Never x -> Never #

Show Never Source # 
Instance details

Defined in Lorentz.Value

Methods

showsPrec :: Int -> Never -> ShowS #

show :: Never -> String #

showList :: [Never] -> ShowS #

NFData Never Source # 
Instance details

Defined in Lorentz.Value

Methods

rnf :: Never -> () #

Buildable Never Source # 
Instance details

Defined in Lorentz.Value

Methods

build :: Never -> Builder #

Eq Never Source # 
Instance details

Defined in Lorentz.Value

Methods

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

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

Ord Never Source # 
Instance details

Defined in Lorentz.Value

Methods

compare :: Never -> Never -> Ordering #

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

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

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

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

max :: Never -> Never -> Never #

min :: Never -> Never -> Never #

HasAnnotation Never Source # 
Instance details

Defined in Lorentz.Value

HasRPCRepr Never Source # 
Instance details

Defined in Lorentz.Value

Associated Types

type AsRPC Never

TypeHasDoc Never Source # 
Instance details

Defined in Lorentz.Value

Associated Types

type TypeDocFieldDescriptions Never :: FieldDescriptions #

IsoValue Never Source # 
Instance details

Defined in Lorentz.Value

Associated Types

type ToT Never :: T #

type Rep Never Source # 
Instance details

Defined in Lorentz.Value

type Rep Never = D1 ('MetaData "Never" "Lorentz.Value" "lorentz-0.15.0-inplace" 'False) (V1 :: Type -> Type)
type AsRPC Never Source # 
Instance details

Defined in Lorentz.Value

type AsRPC Never = Never
type TypeDocFieldDescriptions Never Source # 
Instance details

Defined in Lorentz.Value

type ToT Never Source # 
Instance details

Defined in Lorentz.Value

type ToT Never = GValueType (Rep Never)

data Timestamp #

Instances

Instances details
FromJSON Timestamp 
Instance details

Defined in Morley.Tezos.Core

ToJSON Timestamp 
Instance details

Defined in Morley.Tezos.Core

Data Timestamp 
Instance details

Defined in Morley.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 #

Generic Timestamp 
Instance details

Defined in Morley.Tezos.Core

Associated Types

type Rep Timestamp :: Type -> Type #

Show Timestamp 
Instance details

Defined in Morley.Tezos.Core

NFData Timestamp 
Instance details

Defined in Morley.Tezos.Core

Methods

rnf :: Timestamp -> () #

Buildable Timestamp 
Instance details

Defined in Morley.Tezos.Core

Methods

build :: Timestamp -> Builder #

Eq Timestamp 
Instance details

Defined in Morley.Tezos.Core

Ord Timestamp 
Instance details

Defined in Morley.Tezos.Core

HasAnnotation Timestamp Source # 
Instance details

Defined in Lorentz.Annotation

HasRPCRepr Timestamp 
Instance details

Defined in Morley.AsRPC

Associated Types

type AsRPC Timestamp

TypeHasDoc Timestamp 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions Timestamp :: FieldDescriptions #

IsoValue Timestamp 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT Timestamp :: T #

r ~ Timestamp => ArithOpHs Add Timestamp Integer r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Timestamp ': (Integer ': s)) :-> (r ': s) Source #

r ~ Timestamp => ArithOpHs Add Integer Timestamp r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Timestamp ': s)) :-> (r ': s) Source #

r ~ Integer => ArithOpHs Sub Timestamp Timestamp r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Timestamp ': (Timestamp ': s)) :-> (r ': s) Source #

r ~ Timestamp => ArithOpHs Sub Timestamp Integer r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Timestamp ': (Integer ': s)) :-> (r ': s) Source #

type Rep Timestamp 
Instance details

Defined in Morley.Tezos.Core

type Rep Timestamp = D1 ('MetaData "Timestamp" "Morley.Tezos.Core" "morley-1.19.0-inplace" 'True) (C1 ('MetaCons "Timestamp" 'PrefixI 'True) (S1 ('MetaSel ('Just "unTimestamp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 POSIXTime)))
type AsRPC Timestamp 
Instance details

Defined in Morley.AsRPC

type AsRPC Timestamp = Timestamp
type TypeDocFieldDescriptions Timestamp 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

type ToT Timestamp 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

type ToT Timestamp = 'TTimestamp

data ChainId #

Instances

Instances details
FromJSON ChainId 
Instance details

Defined in Morley.Tezos.Core

ToJSON ChainId 
Instance details

Defined in Morley.Tezos.Core

Generic ChainId 
Instance details

Defined in Morley.Tezos.Core

Associated Types

type Rep ChainId :: Type -> Type #

Methods

from :: ChainId -> Rep ChainId x #

to :: Rep ChainId x -> ChainId #

Show ChainId 
Instance details

Defined in Morley.Tezos.Core

NFData ChainId 
Instance details

Defined in Morley.Tezos.Core

Methods

rnf :: ChainId -> () #

Buildable ChainId 
Instance details

Defined in Morley.Tezos.Core

Methods

build :: ChainId -> Builder #

Eq ChainId 
Instance details

Defined in Morley.Tezos.Core

Methods

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

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

Ord ChainId 
Instance details

Defined in Morley.Tezos.Core

HasAnnotation ChainId Source # 
Instance details

Defined in Lorentz.Annotation

HasRPCRepr ChainId 
Instance details

Defined in Morley.AsRPC

Associated Types

type AsRPC ChainId

TypeHasDoc ChainId 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions ChainId :: FieldDescriptions #

IsoValue ChainId 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT ChainId :: T #

type Rep ChainId 
Instance details

Defined in Morley.Tezos.Core

type Rep ChainId = D1 ('MetaData "ChainId" "Morley.Tezos.Core" "morley-1.19.0-inplace" 'True) (C1 ('MetaCons "UnsafeChainId" 'PrefixI 'True) (S1 ('MetaSel ('Just "unChainId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))
type AsRPC ChainId 
Instance details

Defined in Morley.AsRPC

type AsRPC ChainId = ChainId
type TypeDocFieldDescriptions ChainId 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

type ToT ChainId 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

type ToT ChainId = 'TChainId

type KeyHash = Hash 'HashKindPublicKey #

data PublicKey #

Instances

Instances details
FromJSON PublicKey 
Instance details

Defined in Morley.Tezos.Crypto

ToJSON PublicKey 
Instance details

Defined in Morley.Tezos.Crypto

Generic PublicKey 
Instance details

Defined in Morley.Tezos.Crypto

Associated Types

type Rep PublicKey :: Type -> Type #

Show PublicKey 
Instance details

Defined in Morley.Tezos.Crypto

NFData PublicKey 
Instance details

Defined in Morley.Tezos.Crypto

Methods

rnf :: PublicKey -> () #

Buildable PublicKey 
Instance details

Defined in Morley.Tezos.Crypto

Methods

build :: PublicKey -> Builder #

Eq PublicKey 
Instance details

Defined in Morley.Tezos.Crypto

Ord PublicKey 
Instance details

Defined in Morley.Tezos.Crypto

HasAnnotation PublicKey Source # 
Instance details

Defined in Lorentz.Annotation

HasRPCRepr PublicKey 
Instance details

Defined in Morley.AsRPC

Associated Types

type AsRPC PublicKey

TypeHasDoc PublicKey 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions PublicKey :: FieldDescriptions #

IsoValue PublicKey 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT PublicKey :: T #

type Rep PublicKey 
Instance details

Defined in Morley.Tezos.Crypto

type Rep PublicKey = D1 ('MetaData "PublicKey" "Morley.Tezos.Crypto" "morley-1.19.0-inplace" 'False) (C1 ('MetaCons "PublicKeyEd25519" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedUnpack) (Rec0 PublicKey)) :+: (C1 ('MetaCons "PublicKeySecp256k1" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 PublicKey)) :+: C1 ('MetaCons "PublicKeyP256" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 PublicKey))))
type AsRPC PublicKey 
Instance details

Defined in Morley.AsRPC

type AsRPC PublicKey = PublicKey
type TypeDocFieldDescriptions PublicKey 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

type ToT PublicKey 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

type ToT PublicKey = 'TKey

data Signature #

Instances

Instances details
FromJSON Signature 
Instance details

Defined in Morley.Tezos.Crypto

ToJSON Signature 
Instance details

Defined in Morley.Tezos.Crypto

Generic Signature 
Instance details

Defined in Morley.Tezos.Crypto

Associated Types

type Rep Signature :: Type -> Type #

Show Signature 
Instance details

Defined in Morley.Tezos.Crypto

NFData Signature 
Instance details

Defined in Morley.Tezos.Crypto

Methods

rnf :: Signature -> () #

Buildable Signature 
Instance details

Defined in Morley.Tezos.Crypto

Methods

build :: Signature -> Builder #

Eq Signature 
Instance details

Defined in Morley.Tezos.Crypto

Ord Signature 
Instance details

Defined in Morley.Tezos.Crypto

HasAnnotation Signature Source # 
Instance details

Defined in Lorentz.Annotation

HasRPCRepr Signature 
Instance details

Defined in Morley.AsRPC

Associated Types

type AsRPC Signature

TypeHasDoc Signature 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions Signature :: FieldDescriptions #

IsoValue Signature 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT Signature :: T #

type Rep Signature 
Instance details

Defined in Morley.Tezos.Crypto

type Rep Signature = D1 ('MetaData "Signature" "Morley.Tezos.Crypto" "morley-1.19.0-inplace" 'False) ((C1 ('MetaCons "SignatureEd25519" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedUnpack) (Rec0 Signature)) :+: C1 ('MetaCons "SignatureSecp256k1" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Signature))) :+: (C1 ('MetaCons "SignatureP256" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Signature)) :+: C1 ('MetaCons "SignatureGeneric" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ByteString))))
type AsRPC Signature 
Instance details

Defined in Morley.AsRPC

type AsRPC Signature = Signature
type TypeDocFieldDescriptions Signature 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

type ToT Signature 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

type ToT Signature = 'TSignature

data Bls12381Fr #

Instances

Instances details
Bounded Bls12381Fr 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

Enum Bls12381Fr 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

Num Bls12381Fr 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

Fractional Bls12381Fr 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

Integral Bls12381Fr 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

Real Bls12381Fr 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

Show Bls12381Fr 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

NFData Bls12381Fr 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

Methods

rnf :: Bls12381Fr -> () #

Eq Bls12381Fr 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

Ord Bls12381Fr 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

ToIntegerArithOpHs Bls12381Fr Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalToIntOpHs :: forall (s :: [Type]). (Bls12381Fr ': s) :-> (Integer ': s) Source #

HasRPCRepr Bls12381Fr 
Instance details

Defined in Morley.AsRPC

Associated Types

type AsRPC Bls12381Fr

IsoValue Bls12381Fr 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT Bls12381Fr :: T #

CurveObject Bls12381Fr 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

UnaryArithOpHs Neg Bls12381Fr Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Neg Bls12381Fr Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Bls12381Fr ': s) :-> (UnaryArithResHs Neg Bls12381Fr ': s) Source #

MultiplyPoint Bls12381Fr Bls12381G1 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

MultiplyPoint Bls12381Fr Bls12381G2 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

r ~ Bls12381Fr => ArithOpHs Add Bls12381Fr Bls12381Fr r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Bls12381Fr ': (Bls12381Fr ': s)) :-> (r ': s) Source #

r ~ Bls12381Fr => ArithOpHs Mul Bls12381Fr Bls12381Fr r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Bls12381Fr ': (Bls12381Fr ': s)) :-> (r ': s) Source #

r ~ Bls12381G1 => ArithOpHs Mul Bls12381Fr Bls12381G1 r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Bls12381Fr ': (Bls12381G1 ': s)) :-> (r ': s) Source #

r ~ Bls12381G2 => ArithOpHs Mul Bls12381Fr Bls12381G2 r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Bls12381Fr ': (Bls12381G2 ': s)) :-> (r ': s) Source #

r ~ Bls12381Fr => ArithOpHs Mul Bls12381Fr Integer r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Bls12381Fr ': (Integer ': s)) :-> (r ': s) Source #

r ~ Bls12381Fr => ArithOpHs Mul Bls12381Fr Natural r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Bls12381Fr ': (Natural ': s)) :-> (r ': s) Source #

r ~ Bls12381G1 => ArithOpHs Mul Bls12381G1 Bls12381Fr r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Bls12381G1 ': (Bls12381Fr ': s)) :-> (r ': s) Source #

r ~ Bls12381G2 => ArithOpHs Mul Bls12381G2 Bls12381Fr r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Bls12381G2 ': (Bls12381Fr ': s)) :-> (r ': s) Source #

r ~ Bls12381Fr => ArithOpHs Mul Integer Bls12381Fr r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Integer ': (Bls12381Fr ': s)) :-> (r ': s) Source #

r ~ Bls12381Fr => ArithOpHs Mul Natural Bls12381Fr r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Natural ': (Bls12381Fr ': s)) :-> (r ': s) Source #

type AsRPC Bls12381Fr 
Instance details

Defined in Morley.AsRPC

type AsRPC Bls12381Fr = Bls12381Fr
type ToT Bls12381Fr 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

type ToT Bls12381Fr = 'TBls12381Fr
type UnaryArithResHs Neg Bls12381Fr Source # 
Instance details

Defined in Lorentz.Arith

data Bls12381G1 #

Instances

Instances details
Show Bls12381G1 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

NFData Bls12381G1 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

Methods

rnf :: Bls12381G1 -> () #

Eq Bls12381G1 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

HasRPCRepr Bls12381G1 
Instance details

Defined in Morley.AsRPC

Associated Types

type AsRPC Bls12381G1

IsoValue Bls12381G1 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT Bls12381G1 :: T #

CurveObject Bls12381G1 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

UnaryArithOpHs Neg Bls12381G1 Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Neg Bls12381G1 Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Bls12381G1 ': s) :-> (UnaryArithResHs Neg Bls12381G1 ': s) Source #

MultiplyPoint Bls12381Fr Bls12381G1 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

MultiplyPoint Integer Bls12381G1 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

r ~ Bls12381G1 => ArithOpHs Add Bls12381G1 Bls12381G1 r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Bls12381G1 ': (Bls12381G1 ': s)) :-> (r ': s) Source #

r ~ Bls12381G1 => ArithOpHs Mul Bls12381Fr Bls12381G1 r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Bls12381Fr ': (Bls12381G1 ': s)) :-> (r ': s) Source #

r ~ Bls12381G1 => ArithOpHs Mul Bls12381G1 Bls12381Fr r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Bls12381G1 ': (Bls12381Fr ': s)) :-> (r ': s) Source #

type AsRPC Bls12381G1 
Instance details

Defined in Morley.AsRPC

type AsRPC Bls12381G1 = Bls12381G1
type ToT Bls12381G1 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

type ToT Bls12381G1 = 'TBls12381G1
type UnaryArithResHs Neg Bls12381G1 Source # 
Instance details

Defined in Lorentz.Arith

data Bls12381G2 #

Instances

Instances details
Show Bls12381G2 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

NFData Bls12381G2 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

Methods

rnf :: Bls12381G2 -> () #

Eq Bls12381G2 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

HasRPCRepr Bls12381G2 
Instance details

Defined in Morley.AsRPC

Associated Types

type AsRPC Bls12381G2

IsoValue Bls12381G2 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT Bls12381G2 :: T #

CurveObject Bls12381G2 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

UnaryArithOpHs Neg Bls12381G2 Source # 
Instance details

Defined in Lorentz.Arith

Associated Types

type UnaryArithResHs Neg Bls12381G2 Source #

Methods

evalUnaryArithOpHs :: forall (s :: [Type]). (Bls12381G2 ': s) :-> (UnaryArithResHs Neg Bls12381G2 ': s) Source #

MultiplyPoint Bls12381Fr Bls12381G2 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

MultiplyPoint Integer Bls12381G2 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

r ~ Bls12381G2 => ArithOpHs Add Bls12381G2 Bls12381G2 r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Bls12381G2 ': (Bls12381G2 ': s)) :-> (r ': s) Source #

r ~ Bls12381G2 => ArithOpHs Mul Bls12381Fr Bls12381G2 r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Bls12381Fr ': (Bls12381G2 ': s)) :-> (r ': s) Source #

r ~ Bls12381G2 => ArithOpHs Mul Bls12381G2 Bls12381Fr r Source # 
Instance details

Defined in Lorentz.Arith

Methods

evalArithOpHs :: forall (s :: [Type]). (Bls12381G2 ': (Bls12381Fr ': s)) :-> (r ': s) Source #

type AsRPC Bls12381G2 
Instance details

Defined in Morley.AsRPC

type AsRPC Bls12381G2 = Bls12381G2
type ToT Bls12381G2 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

type ToT Bls12381G2 = 'TBls12381G2
type UnaryArithResHs Neg Bls12381G2 Source # 
Instance details

Defined in Lorentz.Arith

data Set a #

A set of values a.

Instances

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

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 #

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 #

Hashable1 Set

Since: hashable-1.3.4.0

Instance details

Defined in Data.Hashable.Class

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Set a -> Int #

(NiceComparable a, NiceComparable b) => LorentzFunctor Set a b Source # 
Instance details

Defined in Lorentz.Instr

Methods

lmap :: forall (s :: [Type]). KnownValue b => ('[a] :-> '[b]) -> (Set a ': s) :-> (Set b ': s) Source #

Structured k => Structured (Set k) 
Instance details

Defined in Distribution.Utils.Structured

Methods

structure :: Proxy (Set k) -> Structure #

structureHash' :: Tagged (Set k) MD5

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 #

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

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

NFData a => NFData (Set a) 
Instance details

Defined in Data.Set.Internal

Methods

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

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 #

Hashable v => Hashable (Set v)

Since: hashable-1.3.4.0

Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Set v -> Int #

hash :: Set v -> Int #

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

KnownIsoT v => HasAnnotation (Set v) Source # 
Instance details

Defined in Lorentz.Annotation

LDefault (Set k) Source # 
Instance details

Defined in Lorentz.Default

Methods

ldef :: Set k Source #

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

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 #

SizeOpHs (Set a) Source # 
Instance details

Defined in Lorentz.Polymorphic

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

Defined in Lorentz.Polymorphic

Associated Types

type UpdOpKeyHs (Set a) Source #

type UpdOpParamsHs (Set a) Source #

HasRPCRepr (Set a) 
Instance details

Defined in Morley.AsRPC

Associated Types

type AsRPC (Set a)

PolyCTypeHasDocC '[a] => TypeHasDoc (Set a) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions (Set a) :: FieldDescriptions #

Methods

typeDocName :: Proxy (Set a) -> Text #

typeDocMdDescription :: Markdown #

typeDocMdReference :: Proxy (Set a) -> WithinParens -> Markdown #

typeDocDependencies :: Proxy (Set a) -> [SomeDocDefinitionItem] #

typeDocHaskellRep :: TypeDocHaskellRep (Set a) #

typeDocMichelsonRep :: TypeDocMichelsonRep (Set a) #

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

Defined in Morley.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 #

(Ord a, Monoid a) => Semiring (Set a)

The multiplication laws are satisfied for any underlying Monoid, so we require a Monoid constraint instead of a Semiring constraint since times can use the context of either.

Instance details

Defined in Data.Semiring

Methods

plus :: Set a -> Set a -> Set a #

zero :: Set a #

times :: Set a -> Set a -> Set a #

one :: Set a #

fromNatural :: Natural -> Set a #

Ord v => Container (Set v) 
Instance details

Defined in Universum.Container.Class

Associated Types

type Element (Set v) #

Methods

toList :: Set v -> [Element (Set v)] #

null :: Set v -> Bool #

foldr :: (Element (Set v) -> b -> b) -> b -> Set v -> b #

foldl :: (b -> Element (Set v) -> b) -> b -> Set v -> b #

foldl' :: (b -> Element (Set v) -> b) -> b -> Set v -> b #

length :: Set v -> Int #

elem :: Element (Set v) -> Set v -> Bool #

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 #

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

safeMaximum :: Set v -> Maybe (Element (Set v)) #

safeMinimum :: Set v -> Maybe (Element (Set v)) #

safeFoldr1 :: (Element (Set v) -> Element (Set v) -> Element (Set v)) -> Set v -> Maybe (Element (Set v)) #

safeFoldl1 :: (Element (Set v) -> Element (Set v) -> Element (Set v)) -> Set v -> Maybe (Element (Set v)) #

Ord a => FromList (Set a) 
Instance details

Defined in Universum.Container.Class

Associated Types

type ListElement (Set a) #

type FromListC (Set a) #

Methods

fromList :: [ListElement (Set a)] -> Set a #

One (Set v) 
Instance details

Defined in Universum.Container.Class

Associated Types

type OneItem (Set v) #

Methods

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

(t ~ Set a', Ord a) => Rewrapped (Set a) t

Use wrapping fromList. unwrapping returns a sorted list.

Instance details

Defined in Control.Lens.Wrapped

CanCastTo k1 k2 => CanCastTo (Set k1 :: Type) (Set k2 :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (Set k1) -> Proxy (Set k2) -> () Source #

(NiceComparable key, Ord key, Dupable key) => StoreHasSubmap (Set key) SelfRef key () Source # 
Instance details

Defined in Lorentz.StoreClass

type Item (Set a) 
Instance details

Defined in Data.Set.Internal

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

Defined in Control.Lens.At

type Index (Set a) = a
type IxValue (Set k) 
Instance details

Defined in Control.Lens.At

type IxValue (Set k) = ()
type Unwrapped (Set a) 
Instance details

Defined in Control.Lens.Wrapped

type Unwrapped (Set a) = [a]
type 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
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 AsRPC (Set a) 
Instance details

Defined in Morley.AsRPC

type AsRPC (Set a) = Set a
type TypeDocFieldDescriptions (Set a) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

type ToT (Set c) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

type ToT (Set c) = 'TSet (ToT c)
type Element (Set v) 
Instance details

Defined in Universum.Container.Class

type Element (Set v) = ElementDefault (Set v)
type FromListC (Set a) 
Instance details

Defined in Universum.Container.Class

type FromListC (Set a) = ()
type ListElement (Set a) 
Instance details

Defined in Universum.Container.Class

type ListElement (Set a) = Item (Set a)
type OneItem (Set v) 
Instance details

Defined in Universum.Container.Class

type OneItem (Set v) = v

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

Since: containers-0.6.3.1

Instance details

Defined in Data.Map.Internal

Methods

bifold :: Monoid m => Map m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Map a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Map a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Map a b -> c #

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 #

Hashable2 Map

Since: hashable-1.3.4.0

Instance details

Defined in Data.Hashable.Class

Methods

liftHashWithSalt2 :: (Int -> a -> Int) -> (Int -> b -> Int) -> Int -> Map a b -> Int #

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 #

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 #

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 #

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

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 #

Hashable k => Hashable1 (Map k)

Since: hashable-1.3.4.0

Instance details

Defined in Data.Hashable.Class

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Map k a -> Int #

NiceComparable k => LorentzFunctor (Map k) a b Source # 
Instance details

Defined in Lorentz.Instr

Methods

lmap :: forall (s :: [Type]). KnownValue b => ('[a] :-> '[b]) -> (Map k a ': s) :-> (Map k b ': s) Source #

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

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

Defined in Distribution.Utils.Structured

Methods

structure :: Proxy (Map k v) -> Structure #

structureHash' :: Tagged (Map k v) MD5

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

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

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

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

Defined in Data.Map.Internal

Methods

rnf :: Map k a -> () #

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

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

(Hashable k, Hashable v) => Hashable (Map k v)

Since: hashable-1.3.4.0

Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Map k v -> Int #

hash :: Map k v -> Int #

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

(HasAnnotation k, HasAnnotation v) => HasAnnotation (Map k v) Source # 
Instance details

Defined in Lorentz.Annotation

LDefault (Map k v) Source # 
Instance details

Defined in Lorentz.Default

Methods

ldef :: Map k v Source #

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

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

SizeOpHs (Map k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

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 #

HasRPCRepr v => HasRPCRepr (Map k v) 
Instance details

Defined in Morley.AsRPC

Associated Types

type AsRPC (Map k v)

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

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions (Map k v) :: FieldDescriptions #

Methods

typeDocName :: Proxy (Map k v) -> Text #

typeDocMdDescription :: Markdown #

typeDocMdReference :: Proxy (Map k v) -> WithinParens -> Markdown #

typeDocDependencies :: Proxy (Map k v) -> [SomeDocDefinitionItem] #

typeDocHaskellRep :: TypeDocHaskellRep (Map k v) #

typeDocMichelsonRep :: TypeDocMichelsonRep (Map k v) #

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

Defined in Morley.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 #

ToBigMap (Map k v) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToBigMapKey (Map k v)

type ToBigMapValue (Map k v)

Methods

mkBigMap :: Map k v -> BigMap (ToBigMapKey (Map k v)) (ToBigMapValue (Map k v)) #

(Ord k, Monoid k, Semiring v) => Semiring (Map k v)

The multiplication laws are satisfied for any underlying Monoid as the key type, so we require a Monoid constraint instead of a Semiring constraint since times can use the context of either.

Instance details

Defined in Data.Semiring

Methods

plus :: Map k v -> Map k v -> Map k v #

zero :: Map k v #

times :: Map k v -> Map k v -> Map k v #

one :: Map k v #

fromNatural :: Natural -> Map k v #

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 #

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 #

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

safeMaximum :: Map k v -> Maybe (Element (Map k v)) #

safeMinimum :: Map k v -> Maybe (Element (Map k v)) #

safeFoldr1 :: (Element (Map k v) -> Element (Map k v) -> Element (Map k v)) -> Map k v -> Maybe (Element (Map k v)) #

safeFoldl1 :: (Element (Map k v) -> Element (Map k v) -> Element (Map k v)) -> Map k v -> Maybe (Element (Map k v)) #

Ord k => FromList (Map k v) 
Instance details

Defined in Universum.Container.Class

Associated Types

type ListElement (Map k v) #

type FromListC (Map k v) #

Methods

fromList :: [ListElement (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 #

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

(t ~ Map k' a', Ord k) => Rewrapped (Map k a) t

Use wrapping fromList. unwrapping returns a sorted list.

Instance details

Defined in Control.Lens.Wrapped

(NiceComparable key, KnownValue value) => StoreHasSubmap (Map key value) SelfRef key value Source # 
Instance details

Defined in Lorentz.StoreClass

Methods

storeSubmapOps :: StoreSubmapOps (Map key value) SelfRef key value Source #

type Item (Map k v) 
Instance details

Defined in Data.Map.Internal

type Item (Map k v) = (k, v)
type Index (Map k a) 
Instance details

Defined in Control.Lens.At

type Index (Map k a) = k
type IxValue (Map k a) 
Instance details

Defined in Control.Lens.At

type IxValue (Map k a) = a
type Unwrapped (Map k a) 
Instance details

Defined in Control.Lens.Wrapped

type Unwrapped (Map k a) = [(k, a)]
type 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 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
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 AsRPC (Map k v) 
Instance details

Defined in Morley.AsRPC

type AsRPC (Map k v) = Map k (AsRPC v)
type TypeDocFieldDescriptions (Map k v) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

type TypeDocFieldDescriptions (Map k v) = '[] :: [(Symbol, (Maybe Symbol, [(Symbol, Symbol)]))]
type ToBigMapKey (Map k v) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

type ToBigMapKey (Map k v) = k
type ToBigMapValue (Map k v) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

type ToBigMapValue (Map k v) = v
type ToT (Map k v) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

type ToT (Map k v) = 'TMap (ToT k) (ToT v)
type Element (Map k v) 
Instance details

Defined in Universum.Container.Class

type Element (Map k v) = ElementDefault (Map k v)
type FromListC (Map k v) 
Instance details

Defined in Universum.Container.Class

type FromListC (Map k v) = ()
type Key (Map k v) 
Instance details

Defined in Universum.Container.Class

type Key (Map k v) = k
type ListElement (Map k v) 
Instance details

Defined in Universum.Container.Class

type ListElement (Map k v) = Item (Map k v)
type OneItem (Map k v) 
Instance details

Defined in Universum.Container.Class

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

Defined in Universum.Container.Class

type Val (Map k v) = v

newtype BigMapId (k2 :: k) (v :: k1) #

Constructors

BigMapId 

Fields

Instances

Instances details
(Typeable k2, Typeable v, Typeable k1, Typeable k3) => Data (BigMapId k2 v) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BigMapId k2 v -> c (BigMapId k2 v) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (BigMapId k2 v) #

toConstr :: BigMapId k2 v -> Constr #

dataTypeOf :: BigMapId k2 v -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> BigMapId k2 v -> BigMapId k2 v #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BigMapId k2 v -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BigMapId k2 v -> r #

gmapQ :: (forall d. Data d => d -> u) -> BigMapId k2 v -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BigMapId k2 v -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BigMapId k2 v -> m (BigMapId k2 v) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BigMapId k2 v -> m (BigMapId k2 v) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BigMapId k2 v -> m (BigMapId k2 v) #

Num (BigMapId k2 v) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Methods

(+) :: BigMapId k2 v -> BigMapId k2 v -> BigMapId k2 v #

(-) :: BigMapId k2 v -> BigMapId k2 v -> BigMapId k2 v #

(*) :: BigMapId k2 v -> BigMapId k2 v -> BigMapId k2 v #

negate :: BigMapId k2 v -> BigMapId k2 v #

abs :: BigMapId k2 v -> BigMapId k2 v #

signum :: BigMapId k2 v -> BigMapId k2 v #

fromInteger :: Integer -> BigMapId k2 v #

Show (BigMapId k2 v) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Methods

showsPrec :: Int -> BigMapId k2 v -> ShowS #

show :: BigMapId k2 v -> String #

showList :: [BigMapId k2 v] -> ShowS #

Buildable (BigMapId k2 v) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Methods

build :: BigMapId k2 v -> Builder #

(HasAnnotation k, HasAnnotation v) => HasAnnotation (BigMapId k v) Source # 
Instance details

Defined in Lorentz.Annotation

IsoValue (BigMapId k2 v) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT (BigMapId k2 v) :: T #

Methods

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

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

type ToT (BigMapId k2 v) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

type ToT (BigMapId k2 v) = ToT Natural

data BigMap k v #

Instances

Instances details
Foldable (BigMap k) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Methods

fold :: Monoid m => BigMap k m -> m #

foldMap :: Monoid m => (a -> m) -> BigMap k a -> m #

foldMap' :: Monoid m => (a -> m) -> BigMap k a -> m #

foldr :: (a -> b -> b) -> b -> BigMap k a -> b #

foldr' :: (a -> b -> b) -> b -> BigMap k a -> b #

foldl :: (b -> a -> b) -> b -> BigMap k a -> b #

foldl' :: (b -> a -> b) -> b -> BigMap k a -> b #

foldr1 :: (a -> a -> a) -> BigMap k a -> a #

foldl1 :: (a -> a -> a) -> BigMap k a -> a #

toList :: BigMap k a -> [a] #

null :: BigMap k a -> Bool #

length :: BigMap k a -> Int #

elem :: Eq a => a -> BigMap k a -> Bool #

maximum :: Ord a => BigMap k a -> a #

minimum :: Ord a => BigMap k a -> a #

sum :: Num a => BigMap k a -> a #

product :: Num a => BigMap k a -> a #

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

(Data k, Data v, Ord k) => Data (BigMap k v) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BigMap k v -> c (BigMap k v) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (BigMap k v) #

toConstr :: BigMap k v -> Constr #

dataTypeOf :: BigMap k v -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> BigMap k v -> BigMap k v #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BigMap k v -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BigMap k v -> r #

gmapQ :: (forall d. Data d => d -> u) -> BigMap k v -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BigMap k v -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BigMap k v -> m (BigMap k v) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BigMap k v -> m (BigMap k v) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BigMap k v -> m (BigMap k v) #

Ord k => Semigroup (BigMap k v) 
Instance details

Defined in Morley.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 => IsList (BigMap k v) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type Item (BigMap k v) #

Methods

fromList :: [Item (BigMap k v)] -> BigMap k v #

fromListN :: Int -> [Item (BigMap k v)] -> BigMap k v #

toList :: BigMap k v -> [Item (BigMap k v)] #

Generic (BigMap k v) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type Rep (BigMap k v) :: Type -> Type #

Methods

from :: BigMap k v -> Rep (BigMap k v) x #

to :: Rep (BigMap k v) x -> BigMap k v #

(Show k, Show v) => Show (BigMap k v) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Methods

showsPrec :: Int -> BigMap k v -> ShowS #

show :: BigMap k v -> String #

showList :: [BigMap k v] -> ShowS #

Default (BigMap k v) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Methods

def :: BigMap k v #

(Ord k, Buildable k, Buildable v) => Buildable (BigMap k v) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Methods

build :: BigMap k v -> Builder #

Ord k => At (BigMap k v) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Methods

at :: Index (BigMap k v) -> Lens' (BigMap k v) (Maybe (IxValue (BigMap k v))) #

Ord k => Ixed (BigMap k v) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Methods

ix :: Index (BigMap k v) -> Traversal' (BigMap k v) (IxValue (BigMap k v)) #

(HasAnnotation k, HasAnnotation v) => HasAnnotation (BigMap k v) Source # 
Instance details

Defined in Lorentz.Annotation

NiceComparable k => GetOpHs (BigMap k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

Associated Types

type GetOpKeyHs (BigMap k v) Source #

type GetOpValHs (BigMap k v) Source #

NiceComparable k => MemOpHs (BigMap k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

Associated Types

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

HasRPCRepr (BigMap k v) 
Instance details

Defined in Morley.AsRPC

Associated Types

type AsRPC (BigMap k v)

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

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions (BigMap k v) :: FieldDescriptions #

Methods

typeDocName :: Proxy (BigMap k v) -> Text #

typeDocMdDescription :: Markdown #

typeDocMdReference :: Proxy (BigMap k v) -> WithinParens -> Markdown #

typeDocDependencies :: Proxy (BigMap k v) -> [SomeDocDefinitionItem] #

typeDocHaskellRep :: TypeDocHaskellRep (BigMap k v) #

typeDocMichelsonRep :: TypeDocMichelsonRep (BigMap k v) #

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

Defined in Morley.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 #

Container (BigMap k v) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type Element (BigMap k v) #

Methods

toList :: BigMap k v -> [Element (BigMap k v)] #

null :: BigMap k v -> Bool #

foldr :: (Element (BigMap k v) -> b -> b) -> b -> BigMap k v -> b #

foldl :: (b -> Element (BigMap k v) -> b) -> b -> BigMap k v -> b #

foldl' :: (b -> Element (BigMap k v) -> b) -> b -> BigMap k v -> b #

length :: BigMap k v -> Int #

elem :: Element (BigMap k v) -> BigMap k v -> Bool #

foldMap :: Monoid m => (Element (BigMap k v) -> m) -> BigMap k v -> m #

fold :: BigMap k v -> Element (BigMap k v) #

foldr' :: (Element (BigMap k v) -> b -> b) -> b -> BigMap k v -> b #

notElem :: Element (BigMap k v) -> BigMap k v -> Bool #

all :: (Element (BigMap k v) -> Bool) -> BigMap k v -> Bool #

any :: (Element (BigMap k v) -> Bool) -> BigMap k v -> Bool #

and :: BigMap k v -> Bool #

or :: BigMap k v -> Bool #

find :: (Element (BigMap k v) -> Bool) -> BigMap k v -> Maybe (Element (BigMap k v)) #

safeHead :: BigMap k v -> Maybe (Element (BigMap k v)) #

safeMaximum :: BigMap k v -> Maybe (Element (BigMap k v)) #

safeMinimum :: BigMap k v -> Maybe (Element (BigMap k v)) #

safeFoldr1 :: (Element (BigMap k v) -> Element (BigMap k v) -> Element (BigMap k v)) -> BigMap k v -> Maybe (Element (BigMap k v)) #

safeFoldl1 :: (Element (BigMap k v) -> Element (BigMap k v) -> Element (BigMap k v)) -> BigMap k v -> Maybe (Element (BigMap k v)) #

One (BigMap k v) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type OneItem (BigMap k v) #

Methods

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

(NiceComparable key, KnownValue value) => StoreHasSubmap (BigMap key value) SelfRef key value Source # 
Instance details

Defined in Lorentz.StoreClass

Methods

storeSubmapOps :: StoreSubmapOps (BigMap key value) SelfRef key value Source #

type Item (BigMap k v) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

type Item (BigMap k v) = Item (Map k v)
type Rep (BigMap k v) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

type Rep (BigMap k v) = D1 ('MetaData "BigMap" "Morley.Michelson.Typed.Haskell.Value" "morley-1.19.0-inplace" 'False) (C1 ('MetaCons "BigMap" 'PrefixI 'True) (S1 ('MetaSel ('Just "bmId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe (BigMapId k v))) :*: S1 ('MetaSel ('Just "bmMap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Map k v))))
type Index (BigMap k _1) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

type Index (BigMap k _1) = k
type IxValue (BigMap _1 v) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

type IxValue (BigMap _1 v) = 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 MemOpKeyHs (BigMap k v) Source # 
Instance details

Defined in Lorentz.Polymorphic

type MemOpKeyHs (BigMap k v) = k
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 AsRPC (BigMap k v) 
Instance details

Defined in Morley.AsRPC

type AsRPC (BigMap k v) = BigMapId k v
type TypeDocFieldDescriptions (BigMap k v) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

type ToT (BigMap k v) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

type ToT (BigMap k v) = 'TBigMap (ToT k) (ToT v)
type Element (BigMap k v) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

type Element (BigMap k v) = ElementDefault (BigMap k v)
type OneItem (BigMap k v) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

type OneItem (BigMap k v) = OneItem (Map k v)

mkBigMap :: ToBigMap m => m -> BigMap (ToBigMapKey m) (ToBigMapValue m) #

type Operation = Operation' Instr #

data Maybe a #

The Maybe type encapsulates an optional value. A value of type Maybe a either contains a value of type a (represented as Just a), or it is empty (represented as Nothing). Using Maybe is a good way to deal with errors or exceptional cases without resorting to drastic measures such as error.

The Maybe type is also a monad. It is a simple kind of error monad, where all errors are represented by Nothing. A richer error monad can be built using the Either type.

Constructors

Nothing 
Just a 

Instances

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

MonadFail Maybe

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.Fail

Methods

fail :: String -> 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 #

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 #

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

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

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 #

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 #

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 #

MonadPlus Maybe

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mzero :: Maybe a #

mplus :: Maybe a -> Maybe a -> Maybe a #

MonadFailure Maybe 
Instance details

Defined in Basement.Monad

Associated Types

type Failure Maybe #

Methods

mFail :: Failure Maybe -> Maybe () #

NFData1 Maybe

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> Maybe a -> () #

MonadThrow Maybe 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> Maybe a #

Hashable1 Maybe 
Instance details

Defined in Data.Hashable.Class

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Maybe a -> Int #

KnownNamedFunctor Maybe 
Instance details

Defined in Morley.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 #

SMonadFail Maybe 
Instance details

Defined in Control.Monad.Fail.Singletons

Methods

sFail :: forall a (t :: [Char]). Sing t -> Sing (Apply FailSym0 t) #

PApplicative Maybe 
Instance details

Defined in Control.Monad.Singletons.Internal

Associated Types

type Pure arg :: f a #

type arg <*> arg1 :: f b #

type LiftA2 arg arg1 arg2 :: f c #

type arg *> arg1 :: f b #

type arg <* arg1 :: f a #

PFunctor Maybe 
Instance details

Defined in Control.Monad.Singletons.Internal

Associated Types

type Fmap arg arg1 :: f b #

type arg <$ arg1 :: f a #

PMonad Maybe 
Instance details

Defined in Control.Monad.Singletons.Internal

Associated Types

type arg >>= arg1 :: m b #

type arg >> arg1 :: m b #

type Return arg :: m a #

SAlternative Maybe 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sEmpty :: Sing EmptySym0 #

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

SApplicative Maybe 
Instance details

Defined in Control.Monad.Singletons.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) #

SFunctor Maybe 
Instance details

Defined in Control.Monad.Singletons.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) #

SMonad Maybe 
Instance details

Defined in Control.Monad.Singletons.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) #

SMonadPlus Maybe 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sMzero :: Sing MzeroSym0 #

sMplus :: forall a (t1 :: Maybe a) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Apply (Apply MplusSym0 t1) t2) #

PFoldable Maybe 
Instance details

Defined in Data.Foldable.Singletons

Associated Types

type Fold arg :: m #

type FoldMap arg arg1 :: m #

type Foldr arg arg1 arg2 :: b #

type Foldr' arg arg1 arg2 :: b #

type Foldl arg arg1 arg2 :: b #

type Foldl' arg arg1 arg2 :: b #

type Foldr1 arg arg1 :: a #

type Foldl1 arg arg1 :: a #

type ToList arg :: [a] #

type Null arg :: Bool #

type Length arg :: Nat #

type Elem arg arg1 :: Bool #

type Maximum arg :: a #

type Minimum arg :: a #

type Sum arg :: a #

type Product arg :: a #

SFoldable Maybe 
Instance details

Defined in Data.Foldable.Singletons

Methods

sFold :: forall m (t1 :: Maybe m). SMonoid m => Sing t1 -> Sing (Apply FoldSym0 t1) #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Maybe a). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply FoldMapSym0 t1) t2) #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Maybe a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply FoldrSym0 t1) t2) t3) #

sFoldr' :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Maybe a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply Foldr'Sym0 t1) t2) t3) #

sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Maybe a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply FoldlSym0 t1) t2) t3) #

sFoldl' :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Maybe a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply Foldl'Sym0 t1) t2) t3) #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Apply (Apply Foldr1Sym0 t1) t2) #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Apply (Apply Foldl1Sym0 t1) t2) #

sToList :: forall a (t1 :: Maybe a). Sing t1 -> Sing (Apply ToListSym0 t1) #

sNull :: forall a (t1 :: Maybe a). Sing t1 -> Sing (Apply NullSym0 t1) #

sLength :: forall a (t1 :: Maybe a). Sing t1 -> Sing (Apply LengthSym0 t1) #

sElem :: forall a (t1 :: a) (t2 :: Maybe a). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply ElemSym0 t1) t2) #

sMaximum :: forall a (t1 :: Maybe a). SOrd a => Sing t1 -> Sing (Apply MaximumSym0 t1) #

sMinimum :: forall a (t1 :: Maybe a). SOrd a => Sing t1 -> Sing (Apply MinimumSym0 t1) #

sSum :: forall a (t1 :: Maybe a). SNum a => Sing t1 -> Sing (Apply SumSym0 t1) #

sProduct :: forall a (t1 :: Maybe a). SNum a => Sing t1 -> Sing (Apply ProductSym0 t1) #

PTraversable Maybe 
Instance details

Defined in Data.Traversable.Singletons

Associated Types

type Traverse arg arg1 :: f (t b) #

type SequenceA arg :: f (t a) #

type MapM arg arg1 :: m (t b) #

type Sequence arg :: m (t a) #

STraversable Maybe 
Instance details

Defined in Data.Traversable.Singletons

Methods

sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: Maybe a). SApplicative f => Sing t1 -> Sing t2 -> Sing (Apply (Apply TraverseSym0 t1) t2) #

sSequenceA :: forall (f :: Type -> Type) a (t1 :: Maybe (f a)). SApplicative f => Sing t1 -> Sing (Apply SequenceASym0 t1) #

sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: Maybe a). SMonad m => Sing t1 -> Sing t2 -> Sing (Apply (Apply MapMSym0 t1) t2) #

sSequence :: forall (m :: Type -> Type) a (t1 :: Maybe (m a)). SMonad m => Sing t1 -> Sing (Apply SequenceSym0 t1) #

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 #

LorentzFunctor Maybe a b Source # 
Instance details

Defined in Lorentz.Instr

Methods

lmap :: forall (s :: [Type]). KnownValue b => ('[a] :-> '[b]) -> (Maybe a ': s) :-> (Maybe b ': s) Source #

(Selector s, GToJSON' enc arity (K1 i (Maybe a) :: Type -> Type), KeyValuePair enc pairs, Monoid pairs) => RecordToPairs enc pairs arity (S1 s (K1 i (Maybe a) :: Type -> Type)) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

recordToPairs :: Options -> ToArgs enc arity a0 -> S1 s (K1 i (Maybe a)) a0 -> pairs

() :=> (Alternative Maybe) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Alternative Maybe #

() :=> (Applicative Maybe) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Applicative Maybe #

() :=> (Functor Maybe) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Functor Maybe #

() :=> (MonadPlus Maybe) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- MonadPlus Maybe #

Lift a => Lift (Maybe a :: Type) 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Maybe a -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Maybe a -> Code m (Maybe a) #

(KnownNat a, KnownNat b, KnownNat r) => ArithOpHs Div (Fixed (BinBase a)) (Fixed (BinBase b)) (Maybe (Fixed (BinBase r))) Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Fixed (BinBase a) ': (Fixed (BinBase b) ': s)) :-> (Maybe (Fixed (BinBase r)) ': s) Source #

(KnownNat a, KnownNat b, KnownNat r) => ArithOpHs Div (Fixed (DecBase a)) (Fixed (DecBase b)) (Maybe (Fixed (DecBase r))) Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (Fixed (DecBase a) ': (Fixed (DecBase b) ': s)) :-> (Maybe (Fixed (DecBase r)) ': s) Source #

(KnownNat a, KnownNat b, KnownNat r) => ArithOpHs Div (NFixed (BinBase a)) (NFixed (BinBase b)) (Maybe (NFixed (BinBase r))) Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (NFixed (BinBase a) ': (NFixed (BinBase b) ': s)) :-> (Maybe (NFixed (BinBase r)) ': s) Source #

(KnownNat a, KnownNat b, KnownNat r) => ArithOpHs Div (NFixed (DecBase a)) (NFixed (DecBase b)) (Maybe (NFixed (DecBase r))) Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

evalArithOpHs :: forall (s :: [Type]). (NFixed (DecBase a) ': (NFixed (DecBase b) ': s)) :-> (Maybe (NFixed (DecBase r)) ': s) Source #

Structured a => Structured (Maybe a) 
Instance details

Defined in Distribution.Utils.Structured

Methods

structure :: Proxy (Maybe a) -> Structure #

structureHash' :: Tagged (Maybe a) MD5

ToJSON a => ToJSON (Maybe a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

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

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 #

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 #

Generic (Maybe a) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Maybe a) :: Type -> Type #

Methods

from :: Maybe a -> Rep (Maybe a) x #

to :: Rep (Maybe a) x -> Maybe a #

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)

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 #

Default (Maybe a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Maybe a #

NFData a => NFData (Maybe a) 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Maybe a -> () #

Buildable a => Buildable (Maybe a) 
Instance details

Defined in Formatting.Buildable

Methods

build :: Maybe a -> Builder #

Eq a => Eq (Maybe a)

Since: base-2.1

Instance details

Defined in GHC.Maybe

Methods

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

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

Ord a => Ord (Maybe a)

Since: base-2.1

Instance details

Defined in GHC.Maybe

Methods

compare :: Maybe a -> Maybe a -> Ordering #

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

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

(>) :: Maybe a -> Maybe a -> Bool #

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

max :: Maybe a -> Maybe a -> Maybe a #

min :: Maybe a -> Maybe a -> Maybe a #

Hashable a => Hashable (Maybe a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Maybe a -> Int #

hash :: Maybe a -> Int #

At (Maybe a) 
Instance details

Defined in Control.Lens.At

Methods

at :: Index (Maybe a) -> Lens' (Maybe a) (Maybe (IxValue (Maybe a))) #

Ixed (Maybe a) 
Instance details

Defined in Control.Lens.At

Methods

ix :: Index (Maybe a) -> Traversal' (Maybe a) (IxValue (Maybe a)) #

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

Defined in Lorentz.Annotation

MapOpHs (Maybe e) Source # 
Instance details

Defined in Lorentz.Polymorphic

Associated Types

type MapOpInpHs (Maybe e) Source #

type MapOpResHs (Maybe e) :: Type -> Type Source #

HasRPCRepr a => HasRPCRepr (Maybe a) 
Instance details

Defined in Morley.AsRPC

Associated Types

type AsRPC (Maybe a)

PolyTypeHasDocC '[a] => TypeHasDoc (Maybe a) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions (Maybe a) :: FieldDescriptions #

Methods

typeDocName :: Proxy (Maybe a) -> Text #

typeDocMdDescription :: Markdown #

typeDocMdReference :: Proxy (Maybe a) -> WithinParens -> Markdown #

typeDocDependencies :: Proxy (Maybe a) -> [SomeDocDefinitionItem] #

typeDocHaskellRep :: TypeDocHaskellRep (Maybe a) #

typeDocMichelsonRep :: TypeDocMichelsonRep (Maybe a) #

IsoValue a => IsoValue (Maybe a) 
Instance details

Defined in Morley.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 #

Semiring a => Semiring (Maybe a) 
Instance details

Defined in Data.Semiring

Methods

plus :: Maybe a -> Maybe a -> Maybe a #

zero :: Maybe a #

times :: Maybe a -> Maybe a -> Maybe a #

one :: Maybe a #

fromNatural :: Natural -> Maybe a #

PEq (Maybe a) 
Instance details

Defined in Data.Eq.Singletons

Associated Types

type arg == arg1 :: Bool #

type arg /= arg1 :: Bool #

SEq a => SEq (Maybe a) 
Instance details

Defined in Data.Eq.Singletons

Methods

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

PMonoid (Maybe a) 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Mempty :: a #

type Mappend arg arg1 :: a #

type Mconcat arg :: a #

SSemigroup a => SMonoid (Maybe a) 
Instance details

Defined in Data.Monoid.Singletons

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

POrd (Maybe a) 
Instance details

Defined in Data.Ord.Singletons

Associated Types

type Compare arg arg1 :: Ordering #

type arg < arg1 :: Bool #

type arg <= arg1 :: Bool #

type arg > arg1 :: Bool #

type arg >= arg1 :: Bool #

type Max arg arg1 :: a #

type Min arg arg1 :: a #

SOrd a => SOrd (Maybe a) 
Instance details

Defined in Data.Ord.Singletons

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

PSemigroup (Maybe a) 
Instance details

Defined in Data.Semigroup.Singletons.Internal

Associated Types

type arg <> arg1 :: a #

type Sconcat arg :: a #

SSemigroup a => SSemigroup (Maybe a) 
Instance details

Defined in Data.Semigroup.Singletons.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) #

PShow (Maybe a) 
Instance details

Defined in Text.Show.Singletons

Associated Types

type ShowsPrec arg arg1 arg2 :: Symbol #

type Show_ arg :: Symbol #

type ShowList arg arg1 :: Symbol #

SShow a => SShow (Maybe a) 
Instance details

Defined in Text.Show.Singletons

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

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

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 #

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

safeMaximum :: Maybe a -> Maybe (Element (Maybe a)) #

safeMinimum :: Maybe a -> Maybe (Element (Maybe a)) #

safeFoldr1 :: (Element (Maybe a) -> Element (Maybe a) -> Element (Maybe a)) -> Maybe a -> Maybe (Element (Maybe a)) #

safeFoldl1 :: (Element (Maybe a) -> Element (Maybe a) -> Element (Maybe a)) -> Maybe a -> Maybe (Element (Maybe a)) #

Pretty a => Pretty (Maybe a) 
Instance details

Defined in Text.PrettyPrint.Leijen.Text

Methods

pretty :: Maybe a -> Doc #

prettyList :: [Maybe a] -> Doc #

Generic1 Maybe 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Maybe :: k -> Type #

Methods

from1 :: forall (a :: k). Maybe a -> Rep1 Maybe a #

to1 :: forall (a :: k). Rep1 Maybe a -> Maybe a #

PMonadFail Maybe 
Instance details

Defined in Control.Monad.Fail.Singletons

Associated Types

type Fail arg :: m a #

PAlternative Maybe 
Instance details

Defined in Control.Monad.Singletons.Internal

Associated Types

type Empty :: f a #

type arg <|> arg1 :: f a #

PMonadPlus Maybe 
Instance details

Defined in Control.Monad.Singletons.Internal

Associated Types

type Mzero :: m a #

type Mplus arg arg1 :: m a #

IsoHKD Maybe (a :: Type) 
Instance details

Defined in Data.Vinyl.XRec

Associated Types

type HKD Maybe a #

Methods

unHKD :: HKD Maybe a -> Maybe a #

toHKD :: Maybe a -> HKD Maybe a #

SDecide a => TestCoercion (SMaybe :: Maybe a -> Type) 
Instance details

Defined in Data.Singletons.Base.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.Base.Instances

Methods

testEquality :: forall (a0 :: k) (b :: k). SMaybe a0 -> SMaybe b -> Maybe (a0 :~: b) #

SingI ('Nothing :: Maybe a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing 'Nothing

(Monoid a) :=> (Monoid (Maybe a)) 
Instance details

Defined in Data.Constraint

Methods

ins :: Monoid a :- Monoid (Maybe a) #

(Semigroup a) :=> (Semigroup (Maybe a)) 
Instance details

Defined in Data.Constraint

Methods

ins :: Semigroup a :- Semigroup (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) #

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

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 (GetFirstSym0 :: TyFun (First a) (Maybe a) -> Type) 
Instance details

Defined in Data.Monoid.Singletons

SingI (GetLastSym0 :: TyFun (Last a) (Maybe a) -> Type) 
Instance details

Defined in Data.Monoid.Singletons

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing FindSym0 #

SingI (GetMaxInternalSym0 :: TyFun (MaxInternal a) (Maybe a) -> Type) 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing GetMaxInternalSym0 #

SingI (GetMinInternalSym0 :: TyFun (MinInternal a) (Maybe a) -> Type) 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing GetMinInternalSym0 #

SingI (FirstSym0 :: TyFun (Maybe a) (First a) -> Type) 
Instance details

Defined in Data.Monoid.Singletons

Methods

sing :: Sing FirstSym0 #

SingI (LastSym0 :: TyFun (Maybe a) (Last a) -> Type) 
Instance details

Defined in Data.Monoid.Singletons

Methods

sing :: Sing LastSym0 #

SingI (MaxInternalSym0 :: TyFun (Maybe a) (MaxInternal a) -> Type) 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing MaxInternalSym0 #

SingI (MinInternalSym0 :: TyFun (Maybe a) (MinInternal a) -> Type) 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing MinInternalSym0 #

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

Defined in Data.Maybe.Singletons

Methods

sing :: Sing IsJustSym0 #

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

Defined in Data.Maybe.Singletons

SingI (MaybeToListSym0 :: TyFun (Maybe a) [a] -> Type) 
Instance details

Defined in Data.Maybe.Singletons

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

Defined in Data.Maybe.Singletons

SingI (CatMaybesSym0 :: TyFun [Maybe a] [a] -> Type) 
Instance details

Defined in Data.Maybe.Singletons

SingI (ListToMaybeSym0 :: TyFun [a] (Maybe a) -> Type) 
Instance details

Defined in Data.Maybe.Singletons

SingI (FromMaybeSym0 :: TyFun a (Maybe a ~> a) -> Type) 
Instance details

Defined in Data.Maybe.Singletons

SEq a => SingI (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Nat) -> Type) 
Instance details

Defined in Data.List.Singletons.Internal

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

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing JustSym0 #

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

Defined in Data.Monoid.Singletons

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

Defined in Data.Monoid.Singletons

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (GetMaxInternalSym0 :: TyFun (MaxInternal a) (Maybe a) -> Type) 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (GetMinInternalSym0 :: TyFun (MinInternal a) (Maybe a) -> Type) 
Instance details

Defined in Data.Foldable.Singletons

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

Defined in Data.Monoid.Singletons

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

Defined in Data.Monoid.Singletons

SuppressUnusedWarnings (Compare_6989586621679180719Sym0 :: TyFun (Maybe a) (Maybe a ~> Ordering) -> Type) 
Instance details

Defined in Data.Ord.Singletons

SuppressUnusedWarnings (TFHelper_6989586621679357720Sym0 :: TyFun (Maybe a) (Maybe a ~> Maybe a) -> Type) 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (TFHelper_6989586621679584139Sym0 :: TyFun (Maybe a) (Maybe a ~> Maybe a) -> Type) 
Instance details

Defined in Data.Semigroup.Singletons.Internal

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

Defined in Data.Eq.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Maybe.Singletons

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

Defined in Data.Maybe.Singletons

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

Defined in Data.Maybe.Singletons

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

Defined in Data.Maybe.Singletons

SuppressUnusedWarnings (ShowsPrec_6989586621680071724Sym0 :: TyFun Nat (Maybe a ~> (Symbol ~> Symbol)) -> Type) 
Instance details

Defined in Text.Show.Singletons

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

Defined in Data.Maybe.Singletons

SuppressUnusedWarnings (Fail_6989586621679456264Sym0 :: TyFun [Char] (Maybe a) -> Type) 
Instance details

Defined in Control.Monad.Fail.Singletons

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.Maybe.Singletons

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

Defined in Data.Maybe.Singletons

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

Defined in Data.List.Singletons.Internal

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

Defined in Control.Monad.Singletons.Internal

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

Defined in Data.Singletons.Base.Instances

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

Defined in Control.Monad.Singletons.Internal

SingI (MapMaybeSym0 :: TyFun (a ~> Maybe b) ([a] ~> [b]) -> Type) 
Instance details

Defined in Data.Maybe.Singletons

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

Defined in Data.Foldable.Singletons

Methods

sing :: Sing FindSym0 #

SingI (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) 
Instance details

Defined in Data.List.Singletons.Internal

SingI d => SingI (FromMaybeSym1 d :: TyFun (Maybe a) a -> Type) 
Instance details

Defined in Data.Maybe.Singletons

Methods

sing :: Sing (FromMaybeSym1 d) #

(SEq a, SingI d) => SingI (ElemIndexSym1 d :: TyFun [a] (Maybe Nat) -> Type) 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ElemIndexSym1 d) #

SingI d => SingI (FindIndexSym1 d :: TyFun [a] (Maybe Nat) -> Type) 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (FindIndexSym1 d) #

SingI d => SingI (FindSym1 d :: TyFun [a] (Maybe a) -> Type) 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (FindSym1 d) #

SEq a => SingI (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing LookupSym0 #

SingI (Maybe_Sym0 :: TyFun b ((a ~> b) ~> (Maybe a ~> b)) -> Type) 
Instance details

Defined in Data.Maybe.Singletons

Methods

sing :: Sing Maybe_Sym0 #

SAlternative f => SingI (OptionalSym0 :: TyFun (f a) (f (Maybe a)) -> Type) 
Instance details

Defined in Control.Applicative.Singletons

SuppressUnusedWarnings (Foldr_6989586621680193829Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (Maybe a ~> b)) -> Type) 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (MapMaybeSym0 :: TyFun (a ~> Maybe b) ([a] ~> [b]) -> Type) 
Instance details

Defined in Data.Maybe.Singletons

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

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (Fmap_6989586621679357336Sym0 :: TyFun (a ~> b) (Maybe a ~> Maybe b) -> Type) 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (FoldMap_6989586621680193813Sym0 :: TyFun (a ~> m) (Maybe a ~> m) -> Type) 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (Foldl_6989586621680193845Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (Maybe a ~> b)) -> Type) 
Instance details

Defined in Data.Foldable.Singletons

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

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (TFHelper_6989586621679357469Sym0 :: TyFun (Maybe (a ~> b)) (Maybe a ~> Maybe b) -> Type) 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (Compare_6989586621679180719Sym1 a6989586621679180724 :: TyFun (Maybe a) Ordering -> Type) 
Instance details

Defined in Data.Ord.Singletons

SuppressUnusedWarnings (TFHelper_6989586621679357633Sym0 :: TyFun (Maybe a) ((a ~> Maybe b) ~> Maybe b) -> Type) 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (TFHelper_6989586621679357496Sym0 :: TyFun (Maybe a) (Maybe b ~> Maybe b) -> Type) 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (TFHelper_6989586621679357644Sym0 :: TyFun (Maybe a) (Maybe b ~> Maybe b) -> Type) 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (ShowsPrec_6989586621680071724Sym1 a6989586621680071734 :: TyFun (Maybe a) (Symbol ~> Symbol) -> Type) 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (TFHelper_6989586621679357720Sym1 a6989586621679357725 :: TyFun (Maybe a) (Maybe a) -> Type) 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (TFHelper_6989586621679584139Sym1 a6989586621679584144 :: TyFun (Maybe a) (Maybe a) -> Type) 
Instance details

Defined in Data.Semigroup.Singletons.Internal

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

Defined in Data.Eq.Singletons

SuppressUnusedWarnings (FromMaybeSym1 a6989586621679486193 :: TyFun (Maybe a) a -> Type) 
Instance details

Defined in Data.Maybe.Singletons

SuppressUnusedWarnings (ElemIndexSym1 a6989586621679731471 :: TyFun [a] (Maybe Nat) -> Type) 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (FindIndexSym1 a6989586621679731453 :: TyFun [a] (Maybe Nat) -> Type) 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (StripPrefixSym1 a6989586621679880880 :: TyFun [a] (Maybe [a]) -> Type) 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (FindSym1 a6989586621679731480 :: TyFun [a] (Maybe a) -> Type) 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (TFHelper_6989586621679357348Sym0 :: TyFun a (Maybe b ~> Maybe a) -> Type) 
Instance details

Defined in Control.Monad.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Maybe_Sym0 :: TyFun b ((a ~> b) ~> (Maybe a ~> b)) -> Type) 
Instance details

Defined in Data.Maybe.Singletons

SuppressUnusedWarnings (OptionalSym0 :: TyFun (f a) (f (Maybe a)) -> Type) 
Instance details

Defined in Control.Applicative.Singletons

SuppressUnusedWarnings (Let6989586621680193772MkJustSym0 :: TyFun k (TyFun a6989586621680192944 (Maybe a6989586621680192944) -> Type) -> Type) 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (Let6989586621680193787MkJustSym0 :: TyFun k (TyFun a6989586621680192945 (Maybe a6989586621680192945) -> Type) -> Type) 
Instance details

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

SingI d => SingI (Maybe_Sym1 d :: TyFun (a ~> b) (Maybe a ~> b) -> Type) 
Instance details

Defined in Data.Maybe.Singletons

Methods

sing :: Sing (Maybe_Sym1 d) #

(SEq a, SingI d) => SingI (LookupSym1 d :: TyFun [(a, b)] (Maybe b) -> Type) 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (LookupSym1 d) #

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

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FindSym1 d) #

SuppressUnusedWarnings (LiftA2_6989586621679357482Sym0 :: TyFun (a ~> (b ~> c)) (Maybe a ~> (Maybe b ~> Maybe c)) -> Type) 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (TFHelper_6989586621679357633Sym1 a6989586621679357638 :: TyFun (a ~> Maybe b) (Maybe b) -> Type) 
Instance details

Defined in Control.Monad.Singletons.Internal

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

Defined in Data.Maybe.Singletons

SuppressUnusedWarnings (Maybe_Sym1 a6989586621679484326 :: TyFun (a ~> b) (Maybe a ~> b) -> Type) 
Instance details

Defined in Data.Maybe.Singletons

SuppressUnusedWarnings (Traverse_6989586621680478666Sym0 :: TyFun (a ~> f b) (Maybe a ~> f (Maybe b)) -> Type) 
Instance details

Defined in Data.Traversable.Singletons

SuppressUnusedWarnings (Let6989586621680193673MfSym0 :: TyFun (k2 ~> (k3 ~> k2)) (TyFun k (TyFun k2 (TyFun (Maybe k3) (Maybe k2) -> Type) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (Let6989586621680193694MfSym0 :: TyFun (k2 ~> (k3 ~> k3)) (TyFun k (TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (Fmap_6989586621679357336Sym1 a6989586621679357341 :: TyFun (Maybe a) (Maybe b) -> Type) 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (TFHelper_6989586621679357469Sym1 a6989586621679357474 :: TyFun (Maybe a) (Maybe b) -> Type) 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (FoldMap_6989586621680193813Sym1 a6989586621680193822 :: TyFun (Maybe a) m -> Type) 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (TFHelper_6989586621679357348Sym1 a6989586621679357353 :: TyFun (Maybe b) (Maybe a) -> Type) 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (TFHelper_6989586621679357496Sym1 a6989586621679357501 :: TyFun (Maybe b) (Maybe b) -> Type) 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (TFHelper_6989586621679357644Sym1 a6989586621679357653 :: TyFun (Maybe b) (Maybe b) -> Type) 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (LookupSym1 a6989586621679731178 :: TyFun [(a, b)] (Maybe b) -> Type) 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Let6989586621680193772MkJustSym1 a_69895866216801937666989586621680193771 :: TyFun a6989586621680192944 (Maybe a6989586621680192944) -> Type) 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (Let6989586621680193787MkJustSym1 a_69895866216801937816989586621680193786 :: TyFun a6989586621680192945 (Maybe a6989586621680192945) -> Type) 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (Foldl_6989586621680193845Sym1 a6989586621680193851 :: TyFun b (Maybe a ~> b) -> Type) 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (Foldr_6989586621680193829Sym1 a6989586621680193835 :: TyFun b (Maybe a ~> b) -> Type) 
Instance details

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Monoid.Singletons

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

Defined in Data.Monoid.Singletons

SuppressUnusedWarnings (Let6989586621680184048NSym1 x6989586621680184046 :: TyFun k1 (Maybe k1) -> Type) 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (Let6989586621680184072NSym1 x6989586621680184070 :: TyFun k1 (Maybe k1) -> Type) 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (FindSym1 a6989586621680193279 :: TyFun (t a) (Maybe a) -> Type) 
Instance details

Defined in Data.Foldable.Singletons

(SingI d1, SingI d2) => SingI (Maybe_Sym2 d1 d2 :: TyFun (Maybe a) b -> Type) 
Instance details

Defined in Data.Maybe.Singletons

Methods

sing :: Sing (Maybe_Sym2 d1 d2) #

SuppressUnusedWarnings (Lambda_6989586621680118497Sym1 a6989586621680118495 :: TyFun (k1 ~> First a) (TyFun k1 (Maybe a) -> Type) -> Type) 
Instance details

Defined in Data.Monoid.Singletons

SuppressUnusedWarnings (Lambda_6989586621680118708Sym1 a6989586621680118706 :: TyFun (k1 ~> Last a) (TyFun k1 (Maybe a) -> Type) -> Type) 
Instance details

Defined in Data.Monoid.Singletons

SuppressUnusedWarnings (LiftA2_6989586621679357482Sym1 a6989586621679357488 :: TyFun (Maybe a) (Maybe b ~> Maybe c) -> Type) 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (Foldl_6989586621680193845Sym2 a6989586621680193851 a6989586621680193852 :: TyFun (Maybe a) b -> Type) 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (Foldr_6989586621680193829Sym2 a6989586621680193835 a6989586621680193836 :: TyFun (Maybe a) b -> Type) 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (Maybe_Sym2 a6989586621679484326 a6989586621679484327 :: TyFun (Maybe a) b -> Type) 
Instance details

Defined in Data.Maybe.Singletons

SuppressUnusedWarnings (Traverse_6989586621680478666Sym1 a6989586621680478671 :: TyFun (Maybe a) (f (Maybe b)) -> Type) 
Instance details

Defined in Data.Traversable.Singletons

SuppressUnusedWarnings (Let6989586621680193694MfSym1 f6989586621680193692 :: TyFun k (TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (Let6989586621680193673MfSym1 f6989586621680193671 :: TyFun k (TyFun k2 (TyFun (Maybe k3) (Maybe k2) -> Type) -> Type) -> Type) 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (LiftA2_6989586621679357482Sym2 a6989586621679357488 a6989586621679357489 :: TyFun (Maybe b) (Maybe c) -> Type) 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (Let6989586621680193694MfSym2 f6989586621680193692 xs6989586621680193693 :: TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (Lambda_6989586621680118497Sym2 a6989586621680118495 k6989586621680118496 :: TyFun k1 (Maybe a) -> Type) 
Instance details

Defined in Data.Monoid.Singletons

SuppressUnusedWarnings (Lambda_6989586621680118708Sym2 a6989586621680118706 k6989586621680118707 :: TyFun k1 (Maybe a) -> Type) 
Instance details

Defined in Data.Monoid.Singletons

SuppressUnusedWarnings (Let6989586621680193673MfSym2 f6989586621680193671 xs6989586621680193672 :: TyFun k2 (TyFun (Maybe k3) (Maybe k2) -> Type) -> Type) 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (Let6989586621680193673MfSym3 f6989586621680193671 xs6989586621680193672 a6989586621680193674 :: TyFun (Maybe k3) (Maybe k2) -> Type) 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (Let6989586621680193694MfSym3 f6989586621680193692 xs6989586621680193693 a6989586621680193695 :: TyFun k3 (Maybe k3) -> Type) 
Instance details

Defined in Data.Foldable.Singletons

(HasAnnotation (Maybe a), KnownSymbol name) => HasAnnotation (NamedF Maybe a name) Source # 
Instance details

Defined in Lorentz.Annotation

Unwrappable (NamedF Maybe a name) Source # 
Instance details

Defined in Lorentz.Wrappable

Associated Types

type Unwrappabled (NamedF Maybe a name) Source #

Wrappable (NamedF Maybe a name) Source # 
Instance details

Defined in Lorentz.Wrappable

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

Defined in Morley.AsRPC

Associated Types

type AsRPC (NamedF Maybe a name)

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

Defined in Morley.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 #

type Failure Maybe 
Instance details

Defined in Basement.Monad

type Failure Maybe = ()
type Pure (a :: k1) 
Instance details

Defined in Control.Monad.Singletons.Internal

type Pure (a :: k1) = Apply (Pure_6989586621679357459Sym0 :: TyFun k1 (Maybe k1) -> Type) a
type Return (arg :: a) 
Instance details

Defined in Control.Monad.Singletons.Internal

type Return (arg :: a) = Apply (Return_6989586621679287165Sym0 :: TyFun a (Maybe a) -> Type) arg
type Fold (arg :: Maybe m) 
Instance details

Defined in Data.Foldable.Singletons

type Fold (arg :: Maybe m) = Apply (Fold_6989586621680193565Sym0 :: TyFun (Maybe m) m -> Type) arg
type Length (arg :: Maybe a) 
Instance details

Defined in Data.Foldable.Singletons

type Length (arg :: Maybe a) = Apply (Length_6989586621680193731Sym0 :: TyFun (Maybe a) Nat -> Type) arg
type Maximum (arg :: Maybe a) 
Instance details

Defined in Data.Foldable.Singletons

type Maximum (arg :: Maybe a) = Apply (Maximum_6989586621680193764Sym0 :: TyFun (Maybe a) a -> Type) arg
type Minimum (arg :: Maybe a) 
Instance details

Defined in Data.Foldable.Singletons

type Minimum (arg :: Maybe a) = Apply (Minimum_6989586621680193779Sym0 :: TyFun (Maybe a) a -> Type) arg
type Null (arg :: Maybe a) 
Instance details

Defined in Data.Foldable.Singletons

type Null (arg :: Maybe a) = Apply (Null_6989586621680193714Sym0 :: TyFun (Maybe a) Bool -> Type) arg
type Product (arg :: Maybe a) 
Instance details

Defined in Data.Foldable.Singletons

type Product (arg :: Maybe a) = Apply (Product_6989586621680193803Sym0 :: TyFun (Maybe a) a -> Type) arg
type Sum (arg :: Maybe a) 
Instance details

Defined in Data.Foldable.Singletons

type Sum (arg :: Maybe a) = Apply (Sum_6989586621680193794Sym0 :: TyFun (Maybe a) a -> Type) arg
type ToList (arg :: Maybe a) 
Instance details

Defined in Data.Foldable.Singletons

type ToList (arg :: Maybe a) = Apply (ToList_6989586621680193705Sym0 :: TyFun (Maybe a) [a] -> Type) arg
type Elem (arg1 :: a) (arg2 :: Maybe a) 
Instance details

Defined in Data.Foldable.Singletons

type Elem (arg1 :: a) (arg2 :: Maybe a) = Apply (Apply (Elem_6989586621680193750Sym0 :: TyFun a (Maybe a ~> Bool) -> Type) arg1) arg2
type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Maybe a) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Maybe a) = Apply (Apply (Foldl1_6989586621680193685Sym0 :: TyFun (a ~> (a ~> a)) (Maybe a ~> a) -> Type) arg1) arg2
type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Maybe a) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Maybe a) = Apply (Apply (Foldr1_6989586621680193664Sym0 :: TyFun (a ~> (a ~> a)) (Maybe a ~> a) -> Type) arg1) arg2
type Sequence (arg :: Maybe (m a)) 
Instance details

Defined in Data.Traversable.Singletons

type Sequence (arg :: Maybe (m a)) = Apply (Sequence_6989586621680471117Sym0 :: TyFun (Maybe (m a)) (m (Maybe a)) -> Type) arg
type SequenceA (arg :: Maybe (f a)) 
Instance details

Defined in Data.Traversable.Singletons

type SequenceA (arg :: Maybe (f a)) = Apply (SequenceA_6989586621680471093Sym0 :: TyFun (Maybe (f a)) (f (Maybe a)) -> Type) arg
type (a2 :: Maybe a1) *> (a3 :: Maybe b) 
Instance details

Defined in Control.Monad.Singletons.Internal

type (a2 :: Maybe a1) *> (a3 :: Maybe b) = Apply (Apply (TFHelper_6989586621679357496Sym0 :: TyFun (Maybe a1) (Maybe b ~> Maybe b) -> Type) a2) a3
type (a1 :: k1) <$ (a2 :: Maybe b) 
Instance details

Defined in Control.Monad.Singletons.Internal

type (a1 :: k1) <$ (a2 :: Maybe b) = Apply (Apply (TFHelper_6989586621679357348Sym0 :: TyFun k1 (Maybe b ~> Maybe k1) -> Type) a1) a2
type (arg1 :: Maybe a) <* (arg2 :: Maybe b) 
Instance details

Defined in Control.Monad.Singletons.Internal

type (arg1 :: Maybe a) <* (arg2 :: Maybe b) = Apply (Apply (TFHelper_6989586621679287120Sym0 :: TyFun (Maybe a) (Maybe b ~> Maybe a) -> Type) arg1) arg2
type (a2 :: Maybe (a1 ~> b)) <*> (a3 :: Maybe a1) 
Instance details

Defined in Control.Monad.Singletons.Internal

type (a2 :: Maybe (a1 ~> b)) <*> (a3 :: Maybe a1) = Apply (Apply (TFHelper_6989586621679357469Sym0 :: TyFun (Maybe (a1 ~> b)) (Maybe a1 ~> Maybe b) -> Type) a2) a3
type (a2 :: Maybe a1) >> (a3 :: Maybe b) 
Instance details

Defined in Control.Monad.Singletons.Internal

type (a2 :: Maybe a1) >> (a3 :: Maybe b) = Apply (Apply (TFHelper_6989586621679357644Sym0 :: TyFun (Maybe a1) (Maybe b ~> Maybe b) -> Type) a2) a3
type (a2 :: Maybe a1) >>= (a3 :: a1 ~> Maybe b) 
Instance details

Defined in Control.Monad.Singletons.Internal

type (a2 :: Maybe a1) >>= (a3 :: a1 ~> Maybe b) = Apply (Apply (TFHelper_6989586621679357633Sym0 :: TyFun (Maybe a1) ((a1 ~> Maybe b) ~> Maybe b) -> Type) a2) a3
type Fmap (a2 :: a1 ~> b) (a3 :: Maybe a1) 
Instance details

Defined in Control.Monad.Singletons.Internal

type Fmap (a2 :: a1 ~> b) (a3 :: Maybe a1) = Apply (Apply (Fmap_6989586621679357336Sym0 :: TyFun (a1 ~> b) (Maybe a1 ~> Maybe b) -> Type) a2) a3
type FoldMap (a2 :: a1 ~> k2) (a3 :: Maybe a1) 
Instance details

Defined in Data.Foldable.Singletons

type FoldMap (a2 :: a1 ~> k2) (a3 :: Maybe a1) = Apply (Apply (FoldMap_6989586621680193813Sym0 :: TyFun (a1 ~> k2) (Maybe a1 ~> k2) -> Type) a2) a3
type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Maybe a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Maybe a1) = Apply (Apply (Apply (Foldl_6989586621680193845Sym0 :: TyFun (k2 ~> (a1 ~> k2)) (k2 ~> (Maybe a1 ~> k2)) -> Type) a2) a3) a4
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Maybe a) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Maybe a) = Apply (Apply (Apply (Foldl'_6989586621680193642Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (Maybe a ~> b)) -> Type) arg1) arg2) arg3
type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Maybe a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Maybe a1) = Apply (Apply (Apply (Foldr_6989586621680193829Sym0 :: TyFun (a1 ~> (k2 ~> k2)) (k2 ~> (Maybe a1 ~> k2)) -> Type) a2) a3) a4
type Foldr' (arg1 :: a ~> (b ~> b)) (arg2 :: b) (arg3 :: Maybe a) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr' (arg1 :: a ~> (b ~> b)) (arg2 :: b) (arg3 :: Maybe a) = Apply (Apply (Apply (Foldr'_6989586621680193604Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (Maybe a ~> b)) -> Type) arg1) arg2) arg3
type MapM (arg1 :: a ~> m b) (arg2 :: Maybe a) 
Instance details

Defined in Data.Traversable.Singletons

type MapM (arg1 :: a ~> m b) (arg2 :: Maybe a) = Apply (Apply (MapM_6989586621680471103Sym0 :: TyFun (a ~> m b) (Maybe a ~> m (Maybe b)) -> Type) arg1) arg2
type Traverse (a2 :: a1 ~> f b) (a3 :: Maybe a1) 
Instance details

Defined in Data.Traversable.Singletons

type Traverse (a2 :: a1 ~> f b) (a3 :: Maybe a1) = Apply (Apply (Traverse_6989586621680478666Sym0 :: TyFun (a1 ~> f b) (Maybe a1 ~> f (Maybe b)) -> Type) a2) a3
type LiftA2 (a2 :: a1 ~> (b ~> c)) (a3 :: Maybe a1) (a4 :: Maybe b) 
Instance details

Defined in Control.Monad.Singletons.Internal

type LiftA2 (a2 :: a1 ~> (b ~> c)) (a3 :: Maybe a1) (a4 :: Maybe b) = Apply (Apply (Apply (LiftA2_6989586621679357482Sym0 :: TyFun (a1 ~> (b ~> c)) (Maybe a1 ~> (Maybe b ~> Maybe c)) -> Type) a2) a3) a4
type Apply (Pure_6989586621679357459Sym0 :: TyFun a (Maybe a) -> Type) (a6989586621679357465 :: a) 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (Pure_6989586621679357459Sym0 :: TyFun a (Maybe a) -> Type) (a6989586621679357465 :: a) = Pure_6989586621679357459 a6989586621679357465
type Apply (JustSym0 :: TyFun a (Maybe a) -> Type) (a6989586621679028273 :: a) 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (JustSym0 :: TyFun a (Maybe a) -> Type) (a6989586621679028273 :: a) = 'Just a6989586621679028273
type Apply (Let6989586621679357729LSym0 :: TyFun k1 (Maybe k1) -> Type) (wild_69895866216793565086989586621679357728 :: k1) 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (Let6989586621679357729LSym0 :: TyFun k1 (Maybe k1) -> Type) (wild_69895866216793565086989586621679357728 :: k1) = Let6989586621679357729L wild_69895866216793565086989586621679357728
type Apply (Let6989586621680193772MkJustSym1 a_69895866216801937666989586621680193771 :: TyFun a (Maybe a) -> Type) (a6989586621680193775 :: a) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Let6989586621680193772MkJustSym1 a_69895866216801937666989586621680193771 :: TyFun a (Maybe a) -> Type) (a6989586621680193775 :: a) = Let6989586621680193772MkJust a_69895866216801937666989586621680193771 a6989586621680193775
type Apply (Let6989586621680193787MkJustSym1 a_69895866216801937816989586621680193786 :: TyFun a (Maybe a) -> Type) (a6989586621680193790 :: a) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Let6989586621680193787MkJustSym1 a_69895866216801937816989586621680193786 :: TyFun a (Maybe a) -> Type) (a6989586621680193790 :: a) = Let6989586621680193787MkJust a_69895866216801937816989586621680193786 a6989586621680193790
type Apply (Let6989586621680184048MSym1 x6989586621680184046 :: TyFun k (Maybe k1) -> Type) (y6989586621680184047 :: k) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Let6989586621680184048MSym1 x6989586621680184046 :: TyFun k (Maybe k1) -> Type) (y6989586621680184047 :: k) = Let6989586621680184048M x6989586621680184046 y6989586621680184047
type Apply (Let6989586621680184072MSym1 x6989586621680184070 :: TyFun k (Maybe k1) -> Type) (y6989586621680184071 :: k) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Let6989586621680184072MSym1 x6989586621680184070 :: TyFun k (Maybe k1) -> Type) (y6989586621680184071 :: k) = Let6989586621680184072M x6989586621680184070 y6989586621680184071
type Apply (Let6989586621680184048NSym1 x6989586621680184046 :: TyFun k1 (Maybe k1) -> Type) (y6989586621680184047 :: k1) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Let6989586621680184048NSym1 x6989586621680184046 :: TyFun k1 (Maybe k1) -> Type) (y6989586621680184047 :: k1) = Let6989586621680184048N x6989586621680184046 y6989586621680184047
type Apply (Let6989586621680184072NSym1 x6989586621680184070 :: TyFun k1 (Maybe k1) -> Type) (y6989586621680184071 :: k1) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Let6989586621680184072NSym1 x6989586621680184070 :: TyFun k1 (Maybe k1) -> Type) (y6989586621680184071 :: k1) = Let6989586621680184072N x6989586621680184070 y6989586621680184071
type Apply (Lambda_6989586621680118497Sym2 a6989586621680118495 k6989586621680118496 :: TyFun k1 (Maybe a) -> Type) (x6989586621680118499 :: k1) 
Instance details

Defined in Data.Monoid.Singletons

type Apply (Lambda_6989586621680118497Sym2 a6989586621680118495 k6989586621680118496 :: TyFun k1 (Maybe a) -> Type) (x6989586621680118499 :: k1) = Lambda_6989586621680118497 a6989586621680118495 k6989586621680118496 x6989586621680118499
type Apply (Lambda_6989586621680118708Sym2 a6989586621680118706 k6989586621680118707 :: TyFun k1 (Maybe a) -> Type) (x6989586621680118710 :: k1) 
Instance details

Defined in Data.Monoid.Singletons

type Apply (Lambda_6989586621680118708Sym2 a6989586621680118706 k6989586621680118707 :: TyFun k1 (Maybe a) -> Type) (x6989586621680118710 :: k1) = Lambda_6989586621680118708 a6989586621680118706 k6989586621680118707 x6989586621680118710
type Apply (Let6989586621680193694MfSym3 f6989586621680193692 xs6989586621680193693 a6989586621680193695 :: TyFun k3 (Maybe k3) -> Type) (a6989586621680193696 :: k3) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Let6989586621680193694MfSym3 f6989586621680193692 xs6989586621680193693 a6989586621680193695 :: TyFun k3 (Maybe k3) -> Type) (a6989586621680193696 :: k3) = Let6989586621680193694Mf f6989586621680193692 xs6989586621680193693 a6989586621680193695 a6989586621680193696
type Apply (ShowsPrec_6989586621680071724Sym0 :: TyFun Nat (Maybe a ~> (Symbol ~> Symbol)) -> Type) (a6989586621680071734 :: Nat) 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsPrec_6989586621680071724Sym0 :: TyFun Nat (Maybe a ~> (Symbol ~> Symbol)) -> Type) (a6989586621680071734 :: Nat) = ShowsPrec_6989586621680071724Sym1 a6989586621680071734 :: TyFun (Maybe a) (Symbol ~> Symbol) -> Type
type Apply (FromMaybeSym0 :: TyFun a (Maybe a ~> a) -> Type) (a6989586621679486193 :: a) 
Instance details

Defined in Data.Maybe.Singletons

type Apply (FromMaybeSym0 :: TyFun a (Maybe a ~> a) -> Type) (a6989586621679486193 :: a) = FromMaybeSym1 a6989586621679486193
type Apply (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Nat) -> Type) (a6989586621679731471 :: a) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Nat) -> Type) (a6989586621679731471 :: a) = ElemIndexSym1 a6989586621679731471
type Apply (TFHelper_6989586621679357348Sym0 :: TyFun a (Maybe b ~> Maybe a) -> Type) (a6989586621679357353 :: a) 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (TFHelper_6989586621679357348Sym0 :: TyFun a (Maybe b ~> Maybe a) -> Type) (a6989586621679357353 :: a) = TFHelper_6989586621679357348Sym1 a6989586621679357353 :: TyFun (Maybe b) (Maybe a) -> Type
type Apply (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) (a6989586621679731178 :: a) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) (a6989586621679731178 :: a) = LookupSym1 a6989586621679731178 :: TyFun [(a, b)] (Maybe b) -> Type
type Apply (Maybe_Sym0 :: TyFun b ((a ~> b) ~> (Maybe a ~> b)) -> Type) (a6989586621679484326 :: b) 
Instance details

Defined in Data.Maybe.Singletons

type Apply (Maybe_Sym0 :: TyFun b ((a ~> b) ~> (Maybe a ~> b)) -> Type) (a6989586621679484326 :: b) = Maybe_Sym1 a6989586621679484326 :: TyFun (a ~> b) (Maybe a ~> b) -> Type
type Apply (Let6989586621680193772MkJustSym0 :: TyFun k (TyFun a6989586621680192944 (Maybe a6989586621680192944) -> Type) -> Type) (a_69895866216801937666989586621680193771 :: k) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Let6989586621680193772MkJustSym0 :: TyFun k (TyFun a6989586621680192944 (Maybe a6989586621680192944) -> Type) -> Type) (a_69895866216801937666989586621680193771 :: k) = Let6989586621680193772MkJustSym1 a_69895866216801937666989586621680193771 :: TyFun a6989586621680192944 (Maybe a6989586621680192944) -> Type
type Apply (Let6989586621680193787MkJustSym0 :: TyFun k (TyFun a6989586621680192945 (Maybe a6989586621680192945) -> Type) -> Type) (a_69895866216801937816989586621680193786 :: k) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Let6989586621680193787MkJustSym0 :: TyFun k (TyFun a6989586621680192945 (Maybe a6989586621680192945) -> Type) -> Type) (a_69895866216801937816989586621680193786 :: k) = Let6989586621680193787MkJustSym1 a_69895866216801937816989586621680193786 :: TyFun a6989586621680192945 (Maybe a6989586621680192945) -> Type
type Apply (Let6989586621680184048NSym0 :: TyFun k (TyFun k1 (Maybe k1) -> Type) -> Type) (x6989586621680184046 :: k) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Let6989586621680184048NSym0 :: TyFun k (TyFun k1 (Maybe k1) -> Type) -> Type) (x6989586621680184046 :: k) = Let6989586621680184048NSym1 x6989586621680184046 :: TyFun k1 (Maybe k1) -> Type
type Apply (Let6989586621680184072NSym0 :: TyFun k (TyFun k1 (Maybe k1) -> Type) -> Type) (x6989586621680184070 :: k) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Let6989586621680184072NSym0 :: TyFun k (TyFun k1 (Maybe k1) -> Type) -> Type) (x6989586621680184070 :: k) = Let6989586621680184072NSym1 x6989586621680184070 :: TyFun k1 (Maybe k1) -> Type
type Apply (Let6989586621680184048MSym0 :: TyFun k1 (TyFun k (Maybe k1) -> Type) -> Type) (x6989586621680184046 :: k1) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Let6989586621680184048MSym0 :: TyFun k1 (TyFun k (Maybe k1) -> Type) -> Type) (x6989586621680184046 :: k1) = Let6989586621680184048MSym1 x6989586621680184046 :: TyFun k (Maybe k1) -> Type
type Apply (Let6989586621680184072MSym0 :: TyFun k1 (TyFun k (Maybe k1) -> Type) -> Type) (x6989586621680184070 :: k1) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Let6989586621680184072MSym0 :: TyFun k1 (TyFun k (Maybe k1) -> Type) -> Type) (x6989586621680184070 :: k1) = Let6989586621680184072MSym1 x6989586621680184070 :: TyFun k (Maybe k1) -> Type
type Apply (Foldl_6989586621680193845Sym1 a6989586621680193851 :: TyFun b (Maybe a ~> b) -> Type) (a6989586621680193852 :: b) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldl_6989586621680193845Sym1 a6989586621680193851 :: TyFun b (Maybe a ~> b) -> Type) (a6989586621680193852 :: b) = Foldl_6989586621680193845Sym2 a6989586621680193851 a6989586621680193852
type Apply (Foldr_6989586621680193829Sym1 a6989586621680193835 :: TyFun b (Maybe a ~> b) -> Type) (a6989586621680193836 :: b) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldr_6989586621680193829Sym1 a6989586621680193835 :: TyFun b (Maybe a ~> b) -> Type) (a6989586621680193836 :: b) = Foldr_6989586621680193829Sym2 a6989586621680193835 a6989586621680193836
type Apply (Lambda_6989586621680118497Sym0 :: TyFun k (TyFun (k1 ~> First a) (TyFun k1 (Maybe a) -> Type) -> Type) -> Type) (a6989586621680118495 :: k) 
Instance details

Defined in Data.Monoid.Singletons

type Apply (Lambda_6989586621680118497Sym0 :: TyFun k (TyFun (k1 ~> First a) (TyFun k1 (Maybe a) -> Type) -> Type) -> Type) (a6989586621680118495 :: k) = Lambda_6989586621680118497Sym1 a6989586621680118495 :: TyFun (k1 ~> First a) (TyFun k1 (Maybe a) -> Type) -> Type
type Apply (Lambda_6989586621680118708Sym0 :: TyFun k (TyFun (k1 ~> Last a) (TyFun k1 (Maybe a) -> Type) -> Type) -> Type) (a6989586621680118706 :: k) 
Instance details

Defined in Data.Monoid.Singletons

type Apply (Lambda_6989586621680118708Sym0 :: TyFun k (TyFun (k1 ~> Last a) (TyFun k1 (Maybe a) -> Type) -> Type) -> Type) (a6989586621680118706 :: k) = Lambda_6989586621680118708Sym1 a6989586621680118706 :: TyFun (k1 ~> Last a) (TyFun k1 (Maybe a) -> Type) -> Type
type Apply (Let6989586621680193694MfSym1 f6989586621680193692 :: TyFun k (TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) -> Type) (xs6989586621680193693 :: k) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Let6989586621680193694MfSym1 f6989586621680193692 :: TyFun k (TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) -> Type) (xs6989586621680193693 :: k) = Let6989586621680193694MfSym2 f6989586621680193692 xs6989586621680193693
type Apply (Let6989586621680193673MfSym1 f6989586621680193671 :: TyFun k (TyFun k2 (TyFun (Maybe k3) (Maybe k2) -> Type) -> Type) -> Type) (xs6989586621680193672 :: k) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Let6989586621680193673MfSym1 f6989586621680193671 :: TyFun k (TyFun k2 (TyFun (Maybe k3) (Maybe k2) -> Type) -> Type) -> Type) (xs6989586621680193672 :: k) = Let6989586621680193673MfSym2 f6989586621680193671 xs6989586621680193672
type Apply (Let6989586621680193673MfSym2 f6989586621680193671 xs6989586621680193672 :: TyFun k2 (TyFun (Maybe k3) (Maybe k2) -> Type) -> Type) (a6989586621680193674 :: k2) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Let6989586621680193673MfSym2 f6989586621680193671 xs6989586621680193672 :: TyFun k2 (TyFun (Maybe k3) (Maybe k2) -> Type) -> Type) (a6989586621680193674 :: k2) = Let6989586621680193673MfSym3 f6989586621680193671 xs6989586621680193672 a6989586621680193674
type Eval (FoldMap f ('Just x) :: a2 -> Type) 
Instance details

Defined in Fcf.Class.Foldable

type Eval (FoldMap f ('Just x) :: a2 -> Type) = Eval (f x)
type Eval (FoldMap f ('Nothing :: Maybe a1) :: a2 -> Type) 
Instance details

Defined in Fcf.Class.Foldable

type Eval (FoldMap f ('Nothing :: Maybe a1) :: a2 -> Type) = MEmpty :: a2
type Eval (Foldr f y ('Just x) :: a2 -> Type) 
Instance details

Defined in Fcf.Class.Foldable

type Eval (Foldr f y ('Just x) :: a2 -> Type) = Eval (f x y)
type Eval (Foldr f y ('Nothing :: Maybe a1) :: a2 -> Type) 
Instance details

Defined in Fcf.Class.Foldable

type Eval (Foldr f y ('Nothing :: Maybe a1) :: a2 -> Type) = y
type DemoteRep (Maybe a) 
Instance details

Defined in GHC.Generics

type DemoteRep (Maybe a) = Maybe (DemoteRep a)
type Rep (Maybe a)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep (Maybe a) = D1 ('MetaData "Maybe" "GHC.Maybe" "base" 'False) (C1 ('MetaCons "Nothing" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Just" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))
data Sing (b :: Maybe a) 
Instance details

Defined in GHC.Generics

data Sing (b :: Maybe a) where
type MEmpty 
Instance details

Defined in Fcf.Class.Monoid

type MEmpty = 'Nothing :: Maybe a
type Index (Maybe a) 
Instance details

Defined in Control.Lens.At

type Index (Maybe a) = ()
type IxValue (Maybe a) 
Instance details

Defined in Control.Lens.At

type IxValue (Maybe a) = a
type MapOpInpHs (Maybe e) Source # 
Instance details

Defined in Lorentz.Polymorphic

type MapOpInpHs (Maybe e) = e
type MapOpResHs (Maybe e) Source # 
Instance details

Defined in Lorentz.Polymorphic

type AsRPC (Maybe a) 
Instance details

Defined in Morley.AsRPC

type AsRPC (Maybe a) = Maybe (AsRPC a)
type TypeDocFieldDescriptions (Maybe a) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

type ToT (Maybe a) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

type ToT (Maybe a) = 'TOption (ToT a)
type Demote (Maybe a) 
Instance details

Defined in Data.Singletons.Base.Instances

type Demote (Maybe a) = Maybe (Demote a)
type Sing 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = SMaybe :: Maybe a -> Type
type Mempty 
Instance details

Defined in Data.Monoid.Singletons

type Mempty = Mempty_6989586621680102643Sym0 :: Maybe a
type Element (Maybe a) 
Instance details

Defined in Universum.Container.Class

type Element (Maybe a) = ElementDefault (Maybe a)
type Rep1 Maybe

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep1 Maybe = D1 ('MetaData "Maybe" "GHC.Maybe" "base" 'False) (C1 ('MetaCons "Nothing" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Just" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Mconcat (arg :: [Maybe a]) 
Instance details

Defined in Data.Monoid.Singletons

type Mconcat (arg :: [Maybe a]) = Apply (Mconcat_6989586621680102596Sym0 :: TyFun [Maybe a] (Maybe a) -> Type) arg
type Sconcat (arg :: NonEmpty (Maybe a)) 
Instance details

Defined in Data.Semigroup.Singletons.Internal

type Sconcat (arg :: NonEmpty (Maybe a)) = Apply (Sconcat_6989586621679583990Sym0 :: TyFun (NonEmpty (Maybe a)) (Maybe a) -> Type) arg
type Show_ (arg :: Maybe a) 
Instance details

Defined in Text.Show.Singletons

type Show_ (arg :: Maybe a) = Apply (Show__6989586621680047550Sym0 :: TyFun (Maybe a) Symbol -> Type) arg
type Empty 
Instance details

Defined in Control.Monad.Singletons.Internal

type Empty = Empty_6989586621679357715Sym0 :: Maybe a
type Mzero 
Instance details

Defined in Control.Monad.Singletons.Internal

type Mzero = Mzero_6989586621679287185Sym0 :: Maybe a
type (arg1 :: Maybe a) /= (arg2 :: Maybe a) 
Instance details

Defined in Data.Eq.Singletons

type (arg1 :: Maybe a) /= (arg2 :: Maybe a) = Apply (Apply (TFHelper_6989586621679127817Sym0 :: TyFun (Maybe a) (Maybe a ~> Bool) -> Type) arg1) arg2
type (a2 :: Maybe a1) == (a3 :: Maybe a1) 
Instance details

Defined in Data.Eq.Singletons

type (a2 :: Maybe a1) == (a3 :: Maybe a1) = Apply (Apply (TFHelper_6989586621679130516Sym0 :: TyFun (Maybe a1) (Maybe a1 ~> Bool) -> Type) a2) a3
type Mappend (arg1 :: Maybe a) (arg2 :: Maybe a) 
Instance details

Defined in Data.Monoid.Singletons

type Mappend (arg1 :: Maybe a) (arg2 :: Maybe a) = Apply (Apply (Mappend_6989586621680102582Sym0 :: TyFun (Maybe a) (Maybe a ~> Maybe a) -> Type) arg1) arg2
type (arg1 :: Maybe a) < (arg2 :: Maybe a) 
Instance details

Defined in Data.Ord.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Ord.Singletons

type (arg1 :: Maybe a) >= (arg2 :: Maybe a) = Apply (Apply (TFHelper_6989586621679166201Sym0 :: TyFun (Maybe a) (Maybe a ~> Bool) -> Type) arg1) arg2
type Compare (a2 :: Maybe a1) (a3 :: Maybe a1) 
Instance details

Defined in Data.Ord.Singletons

type Compare (a2 :: Maybe a1) (a3 :: Maybe a1) = Apply (Apply (Compare_6989586621679180719Sym0 :: TyFun (Maybe a1) (Maybe a1 ~> Ordering) -> Type) a2) a3
type Max (arg1 :: Maybe a) (arg2 :: Maybe a) 
Instance details

Defined in Data.Ord.Singletons

type Max (arg1 :: Maybe a) (arg2 :: Maybe a) = Apply (Apply (Max_6989586621679166217Sym0 :: TyFun (Maybe a) (Maybe a ~> Maybe a) -> Type) arg1) arg2
type Min (arg1 :: Maybe a) (arg2 :: Maybe a) 
Instance details

Defined in Data.Ord.Singletons

type Min (arg1 :: Maybe a) (arg2 :: Maybe a) = Apply (Apply (Min_6989586621679166233Sym0 :: TyFun (Maybe a) (Maybe a ~> Maybe a) -> Type) arg1) arg2
type (a2 :: Maybe a1) <> (a3 :: Maybe a1) 
Instance details

Defined in Data.Semigroup.Singletons.Internal

type (a2 :: Maybe a1) <> (a3 :: Maybe a1) = Apply (Apply (TFHelper_6989586621679584139Sym0 :: TyFun (Maybe a1) (Maybe a1 ~> Maybe a1) -> Type) a2) a3
type ShowList (arg1 :: [Maybe a]) arg2 
Instance details

Defined in Text.Show.Singletons

type ShowList (arg1 :: [Maybe a]) arg2 = Apply (Apply (ShowList_6989586621680047558Sym0 :: TyFun [Maybe a] (Symbol ~> Symbol) -> Type) arg1) arg2
type HKD Maybe (a :: Type) 
Instance details

Defined in Data.Vinyl.XRec

type HKD Maybe (a :: Type) = Maybe a
type Fail a2 
Instance details

Defined in Control.Monad.Fail.Singletons

type Fail a2 = Apply (Fail_6989586621679456264Sym0 :: TyFun [Char] (Maybe a1) -> Type) a2
type ShowsPrec a2 (a3 :: Maybe a1) a4 
Instance details

Defined in Text.Show.Singletons

type ShowsPrec a2 (a3 :: Maybe a1) a4 = Apply (Apply (Apply (ShowsPrec_6989586621680071724Sym0 :: TyFun Nat (Maybe a1 ~> (Symbol ~> Symbol)) -> Type) a2) a3) a4
type (a2 :: Maybe a1) <|> (a3 :: Maybe a1) 
Instance details

Defined in Control.Monad.Singletons.Internal

type (a2 :: Maybe a1) <|> (a3 :: Maybe a1) = Apply (Apply (TFHelper_6989586621679357720Sym0 :: TyFun (Maybe a1) (Maybe a1 ~> Maybe a1) -> Type) a2) a3
type Mplus (arg1 :: Maybe a) (arg2 :: Maybe a) 
Instance details

Defined in Control.Monad.Singletons.Internal

type Mplus (arg1 :: Maybe a) (arg2 :: Maybe a) = Apply (Apply (Mplus_6989586621679287190Sym0 :: TyFun (Maybe a) (Maybe a ~> Maybe a) -> Type) arg1) arg2
type (a2 :: Maybe a1) <> ('Nothing :: Maybe a1) 
Instance details

Defined in Fcf.Class.Monoid

type (a2 :: Maybe a1) <> ('Nothing :: Maybe a1) = a2
type Apply (IsJustSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679486210 :: Maybe a) 
Instance details

Defined in Data.Maybe.Singletons

type Apply (IsJustSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679486210 :: Maybe a) = IsJust a6989586621679486210
type Apply (IsNothingSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679486207 :: Maybe a) 
Instance details

Defined in Data.Maybe.Singletons

type Apply (IsNothingSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679486207 :: Maybe a) = IsNothing a6989586621679486207
type Apply (FromJustSym0 :: TyFun (Maybe a) a -> Type) (a6989586621679486203 :: Maybe a) 
Instance details

Defined in Data.Maybe.Singletons

type Apply (FromJustSym0 :: TyFun (Maybe a) a -> Type) (a6989586621679486203 :: Maybe a) = FromJust a6989586621679486203
type Apply (Compare_6989586621679180719Sym1 a6989586621679180724 :: TyFun (Maybe a) Ordering -> Type) (a6989586621679180725 :: Maybe a) 
Instance details

Defined in Data.Ord.Singletons

type Apply (Compare_6989586621679180719Sym1 a6989586621679180724 :: TyFun (Maybe a) Ordering -> Type) (a6989586621679180725 :: Maybe a) = Compare_6989586621679180719 a6989586621679180724 a6989586621679180725
type Apply (TFHelper_6989586621679130516Sym1 a6989586621679130521 :: TyFun (Maybe a) Bool -> Type) (a6989586621679130522 :: Maybe a) 
Instance details

Defined in Data.Eq.Singletons

type Apply (TFHelper_6989586621679130516Sym1 a6989586621679130521 :: TyFun (Maybe a) Bool -> Type) (a6989586621679130522 :: Maybe a) = TFHelper_6989586621679130516 a6989586621679130521 a6989586621679130522
type Apply (FromMaybeSym1 a6989586621679486193 :: TyFun (Maybe a) a -> Type) (a6989586621679486194 :: Maybe a) 
Instance details

Defined in Data.Maybe.Singletons

type Apply (FromMaybeSym1 a6989586621679486193 :: TyFun (Maybe a) a -> Type) (a6989586621679486194 :: Maybe a) = FromMaybe a6989586621679486193 a6989586621679486194
type Apply (FoldMap_6989586621680193813Sym1 a6989586621680193822 :: TyFun (Maybe a) m -> Type) (a6989586621680193823 :: Maybe a) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldMap_6989586621680193813Sym1 a6989586621680193822 :: TyFun (Maybe a) m -> Type) (a6989586621680193823 :: Maybe a) = FoldMap_6989586621680193813 a6989586621680193822 a6989586621680193823
type Apply (Foldl_6989586621680193845Sym2 a6989586621680193851 a6989586621680193852 :: TyFun (Maybe a) b -> Type) (a6989586621680193853 :: Maybe a) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldl_6989586621680193845Sym2 a6989586621680193851 a6989586621680193852 :: TyFun (Maybe a) b -> Type) (a6989586621680193853 :: Maybe a) = Foldl_6989586621680193845 a6989586621680193851 a6989586621680193852 a6989586621680193853
type Apply (Foldr_6989586621680193829Sym2 a6989586621680193835 a6989586621680193836 :: TyFun (Maybe a) b -> Type) (a6989586621680193837 :: Maybe a) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldr_6989586621680193829Sym2 a6989586621680193835 a6989586621680193836 :: TyFun (Maybe a) b -> Type) (a6989586621680193837 :: Maybe a) = Foldr_6989586621680193829 a6989586621680193835 a6989586621680193836 a6989586621680193837
type Apply (Maybe_Sym2 a6989586621679484326 a6989586621679484327 :: TyFun (Maybe a) b -> Type) (a6989586621679484328 :: Maybe a) 
Instance details

Defined in Data.Maybe.Singletons

type Apply (Maybe_Sym2 a6989586621679484326 a6989586621679484327 :: TyFun (Maybe a) b -> Type) (a6989586621679484328 :: Maybe a) = Maybe_ a6989586621679484326 a6989586621679484327 a6989586621679484328
type ('Nothing :: Maybe a) <> (b :: Maybe a) 
Instance details

Defined in Fcf.Class.Monoid

type ('Nothing :: Maybe a) <> (b :: Maybe a) = b
type Apply (GetFirstSym0 :: TyFun (First a) (Maybe a) -> Type) (a6989586621680107980 :: First a) 
Instance details

Defined in Data.Monoid.Singletons

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

Defined in Data.Monoid.Singletons

type Apply (GetLastSym0 :: TyFun (Last a) (Maybe a) -> Type) (a6989586621680108004 :: Last a) = GetLast a6989586621680108004
type Apply (GetMaxInternalSym0 :: TyFun (MaxInternal a) (Maybe a) -> Type) (a6989586621680182210 :: MaxInternal a) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (GetMaxInternalSym0 :: TyFun (MaxInternal a) (Maybe a) -> Type) (a6989586621680182210 :: MaxInternal a) = GetMaxInternal a6989586621680182210
type Apply (GetMinInternalSym0 :: TyFun (MinInternal a) (Maybe a) -> Type) (a6989586621680182206 :: MinInternal a) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (GetMinInternalSym0 :: TyFun (MinInternal a) (Maybe a) -> Type) (a6989586621680182206 :: MinInternal a) = GetMinInternal a6989586621680182206
type Apply (FirstSym0 :: TyFun (Maybe a) (First a) -> Type) (a6989586621680107977 :: Maybe a) 
Instance details

Defined in Data.Monoid.Singletons

type Apply (FirstSym0 :: TyFun (Maybe a) (First a) -> Type) (a6989586621680107977 :: Maybe a) = 'First a6989586621680107977
type Apply (LastSym0 :: TyFun (Maybe a) (Last a) -> Type) (a6989586621680108001 :: Maybe a) 
Instance details

Defined in Data.Monoid.Singletons

type Apply (LastSym0 :: TyFun (Maybe a) (Last a) -> Type) (a6989586621680108001 :: Maybe a) = 'Last a6989586621680108001
type Apply (MaxInternalSym0 :: TyFun (Maybe a) (MaxInternal a) -> Type) (a6989586621680182200 :: Maybe a) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MaxInternalSym0 :: TyFun (Maybe a) (MaxInternal a) -> Type) (a6989586621680182200 :: Maybe a) = 'MaxInternal a6989586621680182200
type Apply (MinInternalSym0 :: TyFun (Maybe a) (MinInternal a) -> Type) (a6989586621680182203 :: Maybe a) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MinInternalSym0 :: TyFun (Maybe a) (MinInternal a) -> Type) (a6989586621680182203 :: Maybe a) = 'MinInternal a6989586621680182203
type Apply (MaybeToListSym0 :: TyFun (Maybe a) [a] -> Type) (a6989586621679486188 :: Maybe a) 
Instance details

Defined in Data.Maybe.Singletons

type Apply (MaybeToListSym0 :: TyFun (Maybe a) [a] -> Type) (a6989586621679486188 :: Maybe a) = MaybeToList a6989586621679486188
type Apply (CatMaybesSym0 :: TyFun [Maybe a] [a] -> Type) (a6989586621679486178 :: [Maybe a]) 
Instance details

Defined in Data.Maybe.Singletons

type Apply (CatMaybesSym0 :: TyFun [Maybe a] [a] -> Type) (a6989586621679486178 :: [Maybe a]) = CatMaybes a6989586621679486178
type Apply (Fail_6989586621679456264Sym0 :: TyFun [Char] (Maybe a) -> Type) (a6989586621679456268 :: [Char]) 
Instance details

Defined in Control.Monad.Fail.Singletons

type Apply (Fail_6989586621679456264Sym0 :: TyFun [Char] (Maybe a) -> Type) (a6989586621679456268 :: [Char]) = Fail_6989586621679456264 a6989586621679456268 :: Maybe a
type Apply (ListToMaybeSym0 :: TyFun [a] (Maybe a) -> Type) (a6989586621679486184 :: [a]) 
Instance details

Defined in Data.Maybe.Singletons

type Apply (ListToMaybeSym0 :: TyFun [a] (Maybe a) -> Type) (a6989586621679486184 :: [a]) = ListToMaybe a6989586621679486184
type Apply (TFHelper_6989586621679357720Sym1 a6989586621679357725 :: TyFun (Maybe a) (Maybe a) -> Type) (a6989586621679357726 :: Maybe a) 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (TFHelper_6989586621679357720Sym1 a6989586621679357725 :: TyFun (Maybe a) (Maybe a) -> Type) (a6989586621679357726 :: Maybe a) = TFHelper_6989586621679357720 a6989586621679357725 a6989586621679357726
type Apply (TFHelper_6989586621679584139Sym1 a6989586621679584144 :: TyFun (Maybe a) (Maybe a) -> Type) (a6989586621679584145 :: Maybe a) 
Instance details

Defined in Data.Semigroup.Singletons.Internal

type Apply (TFHelper_6989586621679584139Sym1 a6989586621679584144 :: TyFun (Maybe a) (Maybe a) -> Type) (a6989586621679584145 :: Maybe a) = TFHelper_6989586621679584139 a6989586621679584144 a6989586621679584145
type Apply (ElemIndexSym1 a6989586621679731471 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679731472 :: [a]) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ElemIndexSym1 a6989586621679731471 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679731472 :: [a]) = ElemIndex a6989586621679731471 a6989586621679731472
type Apply (FindIndexSym1 a6989586621679731453 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679731454 :: [a]) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (FindIndexSym1 a6989586621679731453 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679731454 :: [a]) = FindIndex a6989586621679731453 a6989586621679731454
type Apply (StripPrefixSym1 a6989586621679880880 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621679880881 :: [a]) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (StripPrefixSym1 a6989586621679880880 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621679880881 :: [a]) = StripPrefix a6989586621679880880 a6989586621679880881
type Apply (FindSym1 a6989586621679731480 :: TyFun [a] (Maybe a) -> Type) (a6989586621679731481 :: [a]) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (FindSym1 a6989586621679731480 :: TyFun [a] (Maybe a) -> Type) (a6989586621679731481 :: [a]) = Find a6989586621679731480 a6989586621679731481
type Apply (OptionalSym0 :: TyFun (f a) (f (Maybe a)) -> Type) (a6989586621680883106 :: f a) 
Instance details

Defined in Control.Applicative.Singletons

type Apply (OptionalSym0 :: TyFun (f a) (f (Maybe a)) -> Type) (a6989586621680883106 :: f a) = Optional a6989586621680883106
type Apply (Fmap_6989586621679357336Sym1 a6989586621679357341 :: TyFun (Maybe a) (Maybe b) -> Type) (a6989586621679357342 :: Maybe a) 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (Fmap_6989586621679357336Sym1 a6989586621679357341 :: TyFun (Maybe a) (Maybe b) -> Type) (a6989586621679357342 :: Maybe a) = Fmap_6989586621679357336 a6989586621679357341 a6989586621679357342
type Apply (TFHelper_6989586621679357469Sym1 a6989586621679357474 :: TyFun (Maybe a) (Maybe b) -> Type) (a6989586621679357475 :: Maybe a) 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (TFHelper_6989586621679357469Sym1 a6989586621679357474 :: TyFun (Maybe a) (Maybe b) -> Type) (a6989586621679357475 :: Maybe a) = TFHelper_6989586621679357469 a6989586621679357474 a6989586621679357475
type Apply (TFHelper_6989586621679357348Sym1 a6989586621679357353 :: TyFun (Maybe b) (Maybe a) -> Type) (a6989586621679357354 :: Maybe b) 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (TFHelper_6989586621679357348Sym1 a6989586621679357353 :: TyFun (Maybe b) (Maybe a) -> Type) (a6989586621679357354 :: Maybe b) = TFHelper_6989586621679357348 a6989586621679357353 a6989586621679357354
type Apply (TFHelper_6989586621679357496Sym1 a6989586621679357501 :: TyFun (Maybe b) (Maybe b) -> Type) (a6989586621679357502 :: Maybe b) 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (TFHelper_6989586621679357496Sym1 a6989586621679357501 :: TyFun (Maybe b) (Maybe b) -> Type) (a6989586621679357502 :: Maybe b) = TFHelper_6989586621679357496 a6989586621679357501 a6989586621679357502
type Apply (TFHelper_6989586621679357644Sym1 a6989586621679357653 :: TyFun (Maybe b) (Maybe b) -> Type) (a6989586621679357654 :: Maybe b) 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (TFHelper_6989586621679357644Sym1 a6989586621679357653 :: TyFun (Maybe b) (Maybe b) -> Type) (a6989586621679357654 :: Maybe b) = TFHelper_6989586621679357644 a6989586621679357653 a6989586621679357654
type Apply (LookupSym1 a6989586621679731178 :: TyFun [(a, b)] (Maybe b) -> Type) (a6989586621679731179 :: [(a, b)]) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (LookupSym1 a6989586621679731178 :: TyFun [(a, b)] (Maybe b) -> Type) (a6989586621679731179 :: [(a, b)]) = Lookup a6989586621679731178 a6989586621679731179
type Apply (FindSym1 a6989586621680193279 :: TyFun (t a) (Maybe a) -> Type) (a6989586621680193280 :: t a) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FindSym1 a6989586621680193279 :: TyFun (t a) (Maybe a) -> Type) (a6989586621680193280 :: t a) = Find a6989586621680193279 a6989586621680193280
type Apply (Traverse_6989586621680478666Sym1 a6989586621680478671 :: TyFun (Maybe a) (f (Maybe b)) -> Type) (a6989586621680478672 :: Maybe a) 
Instance details

Defined in Data.Traversable.Singletons

type Apply (Traverse_6989586621680478666Sym1 a6989586621680478671 :: TyFun (Maybe a) (f (Maybe b)) -> Type) (a6989586621680478672 :: Maybe a) = Traverse_6989586621680478666 a6989586621680478671 a6989586621680478672
type Apply (LiftA2_6989586621679357482Sym2 a6989586621679357488 a6989586621679357489 :: TyFun (Maybe b) (Maybe c) -> Type) (a6989586621679357490 :: Maybe b) 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftA2_6989586621679357482Sym2 a6989586621679357488 a6989586621679357489 :: TyFun (Maybe b) (Maybe c) -> Type) (a6989586621679357490 :: Maybe b) = LiftA2_6989586621679357482 a6989586621679357488 a6989586621679357489 a6989586621679357490
type Apply (Let6989586621680193673MfSym3 f6989586621680193671 xs6989586621680193672 a6989586621680193674 :: TyFun (Maybe k3) (Maybe k2) -> Type) (a6989586621680193675 :: Maybe k3) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Let6989586621680193673MfSym3 f6989586621680193671 xs6989586621680193672 a6989586621680193674 :: TyFun (Maybe k3) (Maybe k2) -> Type) (a6989586621680193675 :: Maybe k3) = Let6989586621680193673Mf f6989586621680193671 xs6989586621680193672 a6989586621680193674 a6989586621680193675
type Eval (Init ('[] :: [a]) :: Maybe [a] -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (Init ('[] :: [a]) :: Maybe [a] -> Type) = 'Nothing :: Maybe [a]
type Eval (Tail (_a ': as) :: Maybe [a] -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (Tail (_a ': as) :: Maybe [a] -> Type) = 'Just as
type Eval (Tail ('[] :: [a]) :: Maybe [a] -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (Tail ('[] :: [a]) :: Maybe [a] -> Type) = 'Nothing :: Maybe [a]
type Eval (Init (a2 ': (b ': as)) :: Maybe [a1] -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (Init (a2 ': (b ': as)) :: Maybe [a1] -> Type) = Eval ((Map (Cons a2) :: Maybe [a1] -> Maybe [a1] -> Type) =<< Init (b ': as))
type Eval (Init '[a2] :: Maybe [a1] -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (Init '[a2] :: Maybe [a1] -> Type) = 'Just ('[] :: [a1])
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 ('[] :: [a]) :: Maybe a -> Type) 
Instance details

Defined in Fcf.Data.List

type Eval (Last ('[] :: [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 (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 Apply (Compare_6989586621679180719Sym0 :: TyFun (Maybe a) (Maybe a ~> Ordering) -> Type) (a6989586621679180724 :: Maybe a) 
Instance details

Defined in Data.Ord.Singletons

type Apply (Compare_6989586621679180719Sym0 :: TyFun (Maybe a) (Maybe a ~> Ordering) -> Type) (a6989586621679180724 :: Maybe a) = Compare_6989586621679180719Sym1 a6989586621679180724
type Apply (TFHelper_6989586621679357720Sym0 :: TyFun (Maybe a) (Maybe a ~> Maybe a) -> Type) (a6989586621679357725 :: Maybe a) 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (TFHelper_6989586621679357720Sym0 :: TyFun (Maybe a) (Maybe a ~> Maybe a) -> Type) (a6989586621679357725 :: Maybe a) = TFHelper_6989586621679357720Sym1 a6989586621679357725
type Apply (TFHelper_6989586621679584139Sym0 :: TyFun (Maybe a) (Maybe a ~> Maybe a) -> Type) (a6989586621679584144 :: Maybe a) 
Instance details

Defined in Data.Semigroup.Singletons.Internal

type Apply (TFHelper_6989586621679584139Sym0 :: TyFun (Maybe a) (Maybe a ~> Maybe a) -> Type) (a6989586621679584144 :: Maybe a) = TFHelper_6989586621679584139Sym1 a6989586621679584144
type Apply (TFHelper_6989586621679130516Sym0 :: TyFun (Maybe a) (Maybe a ~> Bool) -> Type) (a6989586621679130521 :: Maybe a) 
Instance details

Defined in Data.Eq.Singletons

type Apply (TFHelper_6989586621679130516Sym0 :: TyFun (Maybe a) (Maybe a ~> Bool) -> Type) (a6989586621679130521 :: Maybe a) = TFHelper_6989586621679130516Sym1 a6989586621679130521
type Apply (StripPrefixSym0 :: TyFun [a] ([a] ~> Maybe [a]) -> Type) (a6989586621679880880 :: [a]) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (StripPrefixSym0 :: TyFun [a] ([a] ~> Maybe [a]) -> Type) (a6989586621679880880 :: [a]) = StripPrefixSym1 a6989586621679880880
type ('Just a2 :: Maybe a1) <> ('Just b :: Maybe a1) 
Instance details

Defined in Fcf.Class.Monoid

type ('Just a2 :: Maybe a1) <> ('Just b :: Maybe a1) = 'Just (a2 <> b)
type Apply (TFHelper_6989586621679357469Sym0 :: TyFun (Maybe (a ~> b)) (Maybe a ~> Maybe b) -> Type) (a6989586621679357474 :: Maybe (a ~> b)) 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (TFHelper_6989586621679357469Sym0 :: TyFun (Maybe (a ~> b)) (Maybe a ~> Maybe b) -> Type) (a6989586621679357474 :: Maybe (a ~> b)) = TFHelper_6989586621679357469Sym1 a6989586621679357474
type Apply (TFHelper_6989586621679357633Sym0 :: TyFun (Maybe a) ((a ~> Maybe b) ~> Maybe b) -> Type) (a6989586621679357638 :: Maybe a) 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (TFHelper_6989586621679357633Sym0 :: TyFun (Maybe a) ((a ~> Maybe b) ~> Maybe b) -> Type) (a6989586621679357638 :: Maybe a) = TFHelper_6989586621679357633Sym1 a6989586621679357638 :: TyFun (a ~> Maybe b) (Maybe b) -> Type
type Apply (TFHelper_6989586621679357496Sym0 :: TyFun (Maybe a) (Maybe b ~> Maybe b) -> Type) (a6989586621679357501 :: Maybe a) 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (TFHelper_6989586621679357496Sym0 :: TyFun (Maybe a) (Maybe b ~> Maybe b) -> Type) (a6989586621679357501 :: Maybe a) = TFHelper_6989586621679357496Sym1 a6989586621679357501 :: TyFun (Maybe b) (Maybe b) -> Type
type Apply (TFHelper_6989586621679357644Sym0 :: TyFun (Maybe a) (Maybe b ~> Maybe b) -> Type) (a6989586621679357653 :: Maybe a) 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (TFHelper_6989586621679357644Sym0 :: TyFun (Maybe a) (Maybe b ~> Maybe b) -> Type) (a6989586621679357653 :: Maybe a) = TFHelper_6989586621679357644Sym1 a6989586621679357653 :: TyFun (Maybe b) (Maybe b) -> Type
type Apply (ShowsPrec_6989586621680071724Sym1 a6989586621680071734 :: TyFun (Maybe a) (Symbol ~> Symbol) -> Type) (a6989586621680071735 :: Maybe a) 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsPrec_6989586621680071724Sym1 a6989586621680071734 :: TyFun (Maybe a) (Symbol ~> Symbol) -> Type) (a6989586621680071735 :: Maybe a) = ShowsPrec_6989586621680071724Sym2 a6989586621680071734 a6989586621680071735
type Apply (LiftA2_6989586621679357482Sym1 a6989586621679357488 :: TyFun (Maybe a) (Maybe b ~> Maybe c) -> Type) (a6989586621679357489 :: Maybe a) 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftA2_6989586621679357482Sym1 a6989586621679357488 :: TyFun (Maybe a) (Maybe b ~> Maybe c) -> Type) (a6989586621679357489 :: Maybe a) = LiftA2_6989586621679357482Sym2 a6989586621679357488 a6989586621679357489
type Apply (Let6989586621680193694MfSym2 f6989586621680193692 xs6989586621680193693 :: TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) (a6989586621680193695 :: Maybe k2) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Let6989586621680193694MfSym2 f6989586621680193692 xs6989586621680193693 :: TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) (a6989586621680193695 :: Maybe k2) = Let6989586621680193694MfSym3 f6989586621680193692 xs6989586621680193693 a6989586621680193695
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 (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 (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 (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 (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 (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 ('Just x <|> _1 :: Maybe a -> Type) 
Instance details

Defined in Morley.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 Morley.Util.Fcf

type Eval (('Nothing :: Maybe a) <|> m :: Maybe a -> Type) = m
type Eval (Map f ('Just a3) :: Maybe a2 -> Type) 
Instance details

Defined in Fcf.Class.Functor

type Eval (Map f ('Just a3) :: Maybe a2 -> Type) = 'Just (Eval (f a3))
type Eval (Map f ('Nothing :: Maybe a) :: Maybe b -> Type) 
Instance details

Defined in Fcf.Class.Functor

type Eval (Map f ('Nothing :: Maybe a) :: Maybe b -> Type) = 'Nothing :: Maybe b
type Apply (TFHelper_6989586621679357633Sym1 a6989586621679357638 :: TyFun (a ~> Maybe b) (Maybe b) -> Type) (a6989586621679357639 :: a ~> Maybe b) 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (TFHelper_6989586621679357633Sym1 a6989586621679357638 :: TyFun (a ~> Maybe b) (Maybe b) -> Type) (a6989586621679357639 :: a ~> Maybe b) = TFHelper_6989586621679357633 a6989586621679357638 a6989586621679357639
type Apply (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Nat) -> Type) (a6989586621679731453 :: a ~> Bool) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Nat) -> Type) (a6989586621679731453 :: a ~> Bool) = FindIndexSym1 a6989586621679731453
type Apply (FindSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe a) -> Type) (a6989586621679731480 :: a ~> Bool) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (FindSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe a) -> Type) (a6989586621679731480 :: a ~> Bool) = FindSym1 a6989586621679731480
type Apply (Foldr_6989586621680193829Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (Maybe a ~> b)) -> Type) (a6989586621680193835 :: a ~> (b ~> b)) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldr_6989586621680193829Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (Maybe a ~> b)) -> Type) (a6989586621680193835 :: a ~> (b ~> b)) = Foldr_6989586621680193829Sym1 a6989586621680193835
type Apply (MapMaybeSym0 :: TyFun (a ~> Maybe b) ([a] ~> [b]) -> Type) (a6989586621679486163 :: a ~> Maybe b) 
Instance details

Defined in Data.Maybe.Singletons

type Apply (MapMaybeSym0 :: TyFun (a ~> Maybe b) ([a] ~> [b]) -> Type) (a6989586621679486163 :: a ~> Maybe b) = MapMaybeSym1 a6989586621679486163
type Apply (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) (a6989586621680193279 :: a ~> Bool) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) (a6989586621680193279 :: a ~> Bool) = FindSym1 a6989586621680193279 :: TyFun (t a) (Maybe a) -> Type
type Apply (Fmap_6989586621679357336Sym0 :: TyFun (a ~> b) (Maybe a ~> Maybe b) -> Type) (a6989586621679357341 :: a ~> b) 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (Fmap_6989586621679357336Sym0 :: TyFun (a ~> b) (Maybe a ~> Maybe b) -> Type) (a6989586621679357341 :: a ~> b) = Fmap_6989586621679357336Sym1 a6989586621679357341
type Apply (FoldMap_6989586621680193813Sym0 :: TyFun (a ~> m) (Maybe a ~> m) -> Type) (a6989586621680193822 :: a ~> m) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldMap_6989586621680193813Sym0 :: TyFun (a ~> m) (Maybe a ~> m) -> Type) (a6989586621680193822 :: a ~> m) = FoldMap_6989586621680193813Sym1 a6989586621680193822
type Apply (Foldl_6989586621680193845Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (Maybe a ~> b)) -> Type) (a6989586621680193851 :: b ~> (a ~> b)) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldl_6989586621680193845Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (Maybe a ~> b)) -> Type) (a6989586621680193851 :: b ~> (a ~> b)) = Foldl_6989586621680193845Sym1 a6989586621680193851
type Apply (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) (a6989586621679731870 :: b ~> Maybe (a, b)) 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) (a6989586621679731870 :: b ~> Maybe (a, b)) = UnfoldrSym1 a6989586621679731870
type Apply (LiftA2_6989586621679357482Sym0 :: TyFun (a ~> (b ~> c)) (Maybe a ~> (Maybe b ~> Maybe c)) -> Type) (a6989586621679357488 :: a ~> (b ~> c)) 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftA2_6989586621679357482Sym0 :: TyFun (a ~> (b ~> c)) (Maybe a ~> (Maybe b ~> Maybe c)) -> Type) (a6989586621679357488 :: a ~> (b ~> c)) = LiftA2_6989586621679357482Sym1 a6989586621679357488
type Apply (Let6989586621679486168RsSym0 :: TyFun (a ~> Maybe k1) (TyFun k (TyFun [a] [k1] -> Type) -> Type) -> Type) (f6989586621679486165 :: a ~> Maybe k1) 
Instance details

Defined in Data.Maybe.Singletons

type Apply (Let6989586621679486168RsSym0 :: TyFun (a ~> Maybe k1) (TyFun k (TyFun [a] [k1] -> Type) -> Type) -> Type) (f6989586621679486165 :: a ~> Maybe k1) = Let6989586621679486168RsSym1 f6989586621679486165 :: TyFun k (TyFun [a] [k1] -> Type) -> Type
type Apply (Maybe_Sym1 a6989586621679484326 :: TyFun (a ~> b) (Maybe a ~> b) -> Type) (a6989586621679484327 :: a ~> b) 
Instance details

Defined in Data.Maybe.Singletons

type Apply (Maybe_Sym1 a6989586621679484326 :: TyFun (a ~> b) (Maybe a ~> b) -> Type) (a6989586621679484327 :: a ~> b) = Maybe_Sym2 a6989586621679484326 a6989586621679484327
type Apply (Traverse_6989586621680478666Sym0 :: TyFun (a ~> f b) (Maybe a ~> f (Maybe b)) -> Type) (a6989586621680478671 :: a ~> f b) 
Instance details

Defined in Data.Traversable.Singletons

type Apply (Traverse_6989586621680478666Sym0 :: TyFun (a ~> f b) (Maybe a ~> f (Maybe b)) -> Type) (a6989586621680478671 :: a ~> f b) = Traverse_6989586621680478666Sym1 a6989586621680478671
type Apply (Let6989586621680193673MfSym0 :: TyFun (k2 ~> (k3 ~> k2)) (TyFun k (TyFun k2 (TyFun (Maybe k3) (Maybe k2) -> Type) -> Type) -> Type) -> Type) (f6989586621680193671 :: k2 ~> (k3 ~> k2)) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Let6989586621680193673MfSym0 :: TyFun (k2 ~> (k3 ~> k2)) (TyFun k (TyFun k2 (TyFun (Maybe k3) (Maybe k2) -> Type) -> Type) -> Type) -> Type) (f6989586621680193671 :: k2 ~> (k3 ~> k2)) = Let6989586621680193673MfSym1 f6989586621680193671 :: TyFun k (TyFun k2 (TyFun (Maybe k3) (Maybe k2) -> Type) -> Type) -> Type
type Apply (Let6989586621680193694MfSym0 :: TyFun (k2 ~> (k3 ~> k3)) (TyFun k (TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) -> Type) -> Type) (f6989586621680193692 :: k2 ~> (k3 ~> k3)) 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Let6989586621680193694MfSym0 :: TyFun (k2 ~> (k3 ~> k3)) (TyFun k (TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) -> Type) -> Type) (f6989586621680193692 :: k2 ~> (k3 ~> k3)) = Let6989586621680193694MfSym1 f6989586621680193692 :: TyFun k (TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621680118497Sym1 a6989586621680118495 :: TyFun (k1 ~> First a) (TyFun k1 (Maybe a) -> Type) -> Type) (k6989586621680118496 :: k1 ~> First a) 
Instance details

Defined in Data.Monoid.Singletons

type Apply (Lambda_6989586621680118497Sym1 a6989586621680118495 :: TyFun (k1 ~> First a) (TyFun k1 (Maybe a) -> Type) -> Type) (k6989586621680118496 :: k1 ~> First a) = Lambda_6989586621680118497Sym2 a6989586621680118495 k6989586621680118496
type Apply (Lambda_6989586621680118708Sym1 a6989586621680118706 :: TyFun (k1 ~> Last a) (TyFun k1 (Maybe a) -> Type) -> Type) (k6989586621680118707 :: k1 ~> Last a) 
Instance details

Defined in Data.Monoid.Singletons

type Apply (Lambda_6989586621680118708Sym1 a6989586621680118706 :: TyFun (k1 ~> Last a) (TyFun k1 (Maybe a) -> Type) -> Type) (k6989586621680118707 :: k1 ~> Last a) = Lambda_6989586621680118708Sym2 a6989586621680118706 k6989586621680118707
type Unwrappabled (NamedF Maybe a name) Source # 
Instance details

Defined in Lorentz.Wrappable

type Unwrappabled (NamedF Maybe a name) = Maybe a
type AsRPC (NamedF Maybe a name) 
Instance details

Defined in Morley.AsRPC

type AsRPC (NamedF Maybe a name) = NamedF Maybe (AsRPC a) name
type ToT (NamedF Maybe a name) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

type ToT (NamedF Maybe a name) = ToT (Maybe a)

type List = [] Source #

data ReadTicket a Source #

Value returned by READ_TICKET instruction.

Constructors

ReadTicket 

Instances

Instances details
Generic (ReadTicket a) Source # 
Instance details

Defined in Lorentz.Value

Associated Types

type Rep (ReadTicket a) :: Type -> Type #

Methods

from :: ReadTicket a -> Rep (ReadTicket a) x #

to :: Rep (ReadTicket a) x -> ReadTicket a #

Show a => Show (ReadTicket a) Source # 
Instance details

Defined in Lorentz.Value

Eq a => Eq (ReadTicket a) Source # 
Instance details

Defined in Lorentz.Value

Methods

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

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

Ord a => Ord (ReadTicket a) Source # 
Instance details

Defined in Lorentz.Value

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

Defined in Lorentz.Value

Associated Types

type ToT (ReadTicket a) :: T #

type Rep (ReadTicket a) Source # 
Instance details

Defined in Lorentz.Value

type Rep (ReadTicket a) = D1 ('MetaData "ReadTicket" "Lorentz.Value" "lorentz-0.15.0-inplace" 'False) (C1 ('MetaCons "ReadTicket" 'PrefixI 'True) (S1 ('MetaSel ('Just "rtTicketer") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Constrained (NullConstraint :: AddressKind -> Constraint) KindedAddress)) :*: (S1 ('MetaSel ('Just "rtData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Just "rtAmount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Natural))))
type ToT (ReadTicket a) Source # 
Instance details

Defined in Lorentz.Value

type ToT (ReadTicket a) = GValueType (Rep (ReadTicket a))

data ContractRef arg #

Instances

Instances details
cp ~ cp' => FromContractRef cp (ContractRef cp') Source # 
Instance details

Defined in Lorentz.Address

cp ~ cp' => ToContractRef cp (ContractRef cp') Source # 
Instance details

Defined in Lorentz.Address

Show (ContractRef arg) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Methods

showsPrec :: Int -> ContractRef arg -> ShowS #

show :: ContractRef arg -> String #

showList :: [ContractRef arg] -> ShowS #

IsoValue (ContractRef arg) => Buildable (ContractRef arg) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Methods

build :: ContractRef arg -> Builder #

Eq (ContractRef arg) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Methods

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

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

ToAddress (ContractRef cp) Source # 
Instance details

Defined in Lorentz.Address

HasAnnotation a => HasAnnotation (ContractRef a) Source # 
Instance details

Defined in Lorentz.Annotation

HasRPCRepr (ContractRef arg) 
Instance details

Defined in Morley.AsRPC

Associated Types

type AsRPC (ContractRef arg)

PolyTypeHasDocC '[cp] => TypeHasDoc (ContractRef cp) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions (ContractRef cp) :: FieldDescriptions #

(HasNoOpToT arg, HasNoNestedBigMaps (ToT arg), WellTypedToT arg) => IsoValue (ContractRef arg) 
Instance details

Defined in Morley.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 #

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 AsRPC (ContractRef arg) 
Instance details

Defined in Morley.AsRPC

type AsRPC (ContractRef arg) = ContractRef arg
type TypeDocFieldDescriptions (ContractRef cp) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

type ToT (ContractRef arg) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

type ToT (ContractRef arg) = 'TContract (ToT arg)

newtype TAddress (p :: Type) (vd :: Type) Source #

Address which remembers the parameter and views types 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
(cp ~ cp', vd ~ vd') => ToTAddress cp vd (TAddress cp' vd') Source # 
Instance details

Defined in Lorentz.Address

Methods

toTAddress :: TAddress cp' vd' -> TAddress cp vd Source #

CanCastTo Address (TAddress p vd :: Type) Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy Address -> Proxy (TAddress p vd) -> () Source #

(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 vd) Source # 
Instance details

Defined in Lorentz.Address

Methods

toContractRef :: TAddress cp vd -> ContractRef arg Source #

CanCastTo (TAddress p vd :: Type) Address Source # 
Instance details

Defined in Lorentz.Coercions

Methods

castDummy :: Proxy (TAddress p vd) -> Proxy Address -> () Source #

Generic (TAddress p vd) Source # 
Instance details

Defined in Lorentz.Address

Associated Types

type Rep (TAddress p vd) :: Type -> Type #

Methods

from :: TAddress p vd -> Rep (TAddress p vd) x #

to :: Rep (TAddress p vd) x -> TAddress p vd #

Show (TAddress p vd) Source # 
Instance details

Defined in Lorentz.Address

Methods

showsPrec :: Int -> TAddress p vd -> ShowS #

show :: TAddress p vd -> String #

showList :: [TAddress p vd] -> ShowS #

Buildable (TAddress p vd) Source # 
Instance details

Defined in Lorentz.Address

Methods

build :: TAddress p vd -> Builder #

Eq (TAddress p vd) Source # 
Instance details

Defined in Lorentz.Address

Methods

(==) :: TAddress p vd -> TAddress p vd -> Bool #

(/=) :: TAddress p vd -> TAddress p vd -> Bool #

Ord (TAddress p vd) Source # 
Instance details

Defined in Lorentz.Address

Methods

compare :: TAddress p vd -> TAddress p vd -> Ordering #

(<) :: TAddress p vd -> TAddress p vd -> Bool #

(<=) :: TAddress p vd -> TAddress p vd -> Bool #

(>) :: TAddress p vd -> TAddress p vd -> Bool #

(>=) :: TAddress p vd -> TAddress p vd -> Bool #

max :: TAddress p vd -> TAddress p vd -> TAddress p vd #

min :: TAddress p vd -> TAddress p vd -> TAddress p vd #

ToAddress (TAddress cp vd) Source # 
Instance details

Defined in Lorentz.Address

Methods

toAddress :: TAddress cp vd -> Address Source #

HasAnnotation (TAddress p vd) Source # 
Instance details

Defined in Lorentz.Address

HasRPCRepr (TAddress cp vd) Source # 
Instance details

Defined in Lorentz.Address

Associated Types

type AsRPC (TAddress cp vd)

(TypeHasDoc p, ViewsDescriptorHasDoc vd) => TypeHasDoc (TAddress p vd) Source # 
Instance details

Defined in Lorentz.Doc

Associated Types

type TypeDocFieldDescriptions (TAddress p vd) :: FieldDescriptions #

Methods

typeDocName :: Proxy (TAddress p vd) -> Text #

typeDocMdDescription :: Markdown #

typeDocMdReference :: Proxy (TAddress p vd) -> WithinParens -> Markdown #

typeDocDependencies :: Proxy (TAddress p vd) -> [SomeDocDefinitionItem] #

typeDocHaskellRep :: TypeDocHaskellRep (TAddress p vd) #

typeDocMichelsonRep :: TypeDocMichelsonRep (TAddress p vd) #

IsoValue (TAddress p vd) Source # 
Instance details

Defined in Lorentz.Address

Associated Types

type ToT (TAddress p vd) :: T #

Methods

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

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

type Rep (TAddress p vd) Source # 
Instance details

Defined in Lorentz.Address

type Rep (TAddress p vd) = D1 ('MetaData "TAddress" "Lorentz.Address" "lorentz-0.15.0-inplace" 'True) (C1 ('MetaCons "TAddress" 'PrefixI 'True) (S1 ('MetaSel ('Just "unTAddress") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Address)))
type AsRPC (TAddress cp vd) Source # 
Instance details

Defined in Lorentz.Address

type AsRPC (TAddress cp vd) = TAddress cp vd
type TypeDocFieldDescriptions (TAddress p vd) Source # 
Instance details

Defined in Lorentz.Doc

type ToT (TAddress p vd) Source # 
Instance details

Defined in Lorentz.Address

type ToT (TAddress p vd) = GValueType (Rep (TAddress p vd))

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

ToAddress (FutureContract cp) Source # 
Instance details

Defined in Lorentz.Address

HasAnnotation (FutureContract a) Source # 
Instance details

Defined in Lorentz.Address

HasRPCRepr (FutureContract p) Source # 
Instance details

Defined in Lorentz.Address

Associated Types

type AsRPC (FutureContract p)

TypeHasDoc p => TypeHasDoc (FutureContract p) Source # 
Instance details

Defined in Lorentz.Doc

Associated Types

type TypeDocFieldDescriptions (FutureContract p) :: FieldDescriptions #

IsoValue (FutureContract arg) Source # 
Instance details

Defined in Lorentz.Address

Associated Types

type ToT (FutureContract arg) :: T #

CanCastTo (FutureContract p :: Type) EpAddress Source # 
Instance details

Defined in Lorentz.Coercions

type AsRPC (FutureContract p) Source # 
Instance details

Defined in Lorentz.Address

type AsRPC (FutureContract p) = FutureContract p
type TypeDocFieldDescriptions (FutureContract p) Source # 
Instance details

Defined in Lorentz.Doc

type ToT (FutureContract arg) Source # 
Instance details

Defined in Lorentz.Address

data Ticket arg #

Constructors

Ticket 

Fields

Instances

Instances details
Show arg => Show (Ticket arg) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Methods

showsPrec :: Int -> Ticket arg -> ShowS #

show :: Ticket arg -> String #

showList :: [Ticket arg] -> ShowS #

Eq arg => Eq (Ticket arg) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Methods

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

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

HasAnnotation d => HasAnnotation (Ticket d) Source # 
Instance details

Defined in Lorentz.Annotation

NiceComparable d => NonZero (Ticket d) Source # 
Instance details

Defined in Lorentz.Macro

Methods

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

PolyTypeHasDocC '[a] => TypeHasDoc (Ticket a) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions (Ticket a) :: FieldDescriptions #

(Comparable (ToT a), IsoValue a) => IsoValue (Ticket a) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT (Ticket a) :: T #

Methods

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

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

type TypeDocFieldDescriptions (Ticket a) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

type ToT (Ticket a) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

type ToT (Ticket a) = 'TTicket (ToT a)

data Chest #

Instances

Instances details
Generic Chest 
Instance details

Defined in Morley.Tezos.Crypto.Timelock

Associated Types

type Rep Chest :: Type -> Type #

Methods

from :: Chest -> Rep Chest x #

to :: Rep Chest x -> Chest #

Show Chest 
Instance details

Defined in Morley.Tezos.Crypto.Timelock

Methods

showsPrec :: Int -> Chest -> ShowS #

show :: Chest -> String #

showList :: [Chest] -> ShowS #

Binary Chest 
Instance details

Defined in Morley.Tezos.Crypto.Timelock

Methods

put :: Chest -> Put #

get :: Get Chest #

putList :: [Chest] -> Put #

NFData Chest 
Instance details

Defined in Morley.Tezos.Crypto.Timelock

Methods

rnf :: Chest -> () #

Eq Chest 
Instance details

Defined in Morley.Tezos.Crypto.Timelock

Methods

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

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

HasAnnotation Chest Source # 
Instance details

Defined in Lorentz.Annotation

HasRPCRepr Chest 
Instance details

Defined in Morley.AsRPC

Associated Types

type AsRPC Chest

TypeHasDoc Chest 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions Chest :: FieldDescriptions #

IsoValue Chest 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT Chest :: T #

type Rep Chest 
Instance details

Defined in Morley.Tezos.Crypto.Timelock

type Rep Chest = D1 ('MetaData "Chest" "Morley.Tezos.Crypto.Timelock" "morley-1.19.0-inplace" 'False) (C1 ('MetaCons "Chest" 'PrefixI 'True) (S1 ('MetaSel ('Just "chestLockedVal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Locked) :*: (S1 ('MetaSel ('Just "chestPublicModulus") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 PublicModulus) :*: S1 ('MetaSel ('Just "chestCiphertext") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Ciphertext))))
type AsRPC Chest 
Instance details

Defined in Morley.AsRPC

type AsRPC Chest = Chest
type TypeDocFieldDescriptions Chest 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

type ToT Chest 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

type ToT Chest = 'TChest

data ChestKey #

Instances

Instances details
Generic ChestKey 
Instance details

Defined in Morley.Tezos.Crypto.Timelock

Associated Types

type Rep ChestKey :: Type -> Type #

Methods

from :: ChestKey -> Rep ChestKey x #

to :: Rep ChestKey x -> ChestKey #

Show ChestKey 
Instance details

Defined in Morley.Tezos.Crypto.Timelock

Binary ChestKey 
Instance details

Defined in Morley.Tezos.Crypto.Timelock

Methods

put :: ChestKey -> Put #

get :: Get ChestKey #

putList :: [ChestKey] -> Put #

NFData ChestKey 
Instance details

Defined in Morley.Tezos.Crypto.Timelock

Methods

rnf :: ChestKey -> () #

Eq ChestKey 
Instance details

Defined in Morley.Tezos.Crypto.Timelock

HasAnnotation ChestKey Source # 
Instance details

Defined in Lorentz.Annotation

HasRPCRepr ChestKey 
Instance details

Defined in Morley.AsRPC

Associated Types

type AsRPC ChestKey

TypeHasDoc ChestKey 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

Associated Types

type TypeDocFieldDescriptions ChestKey :: FieldDescriptions #

IsoValue ChestKey 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Associated Types

type ToT ChestKey :: T #

type Rep ChestKey 
Instance details

Defined in Morley.Tezos.Crypto.Timelock

type Rep ChestKey = D1 ('MetaData "ChestKey" "Morley.Tezos.Crypto.Timelock" "morley-1.19.0-inplace" 'False) (C1 ('MetaCons "ChestKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "ckUnlockedVal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Unlocked) :*: S1 ('MetaSel ('Just "ckProof") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Proof)))
type AsRPC ChestKey 
Instance details

Defined in Morley.AsRPC

type AsRPC ChestKey = ChestKey
type TypeDocFieldDescriptions ChestKey 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Doc

type ToT ChestKey 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

type ToT ChestKey = 'TChestKey

data OpenChest Source #

Instances

Instances details
Generic OpenChest Source # 
Instance details

Defined in Lorentz.Value

Associated Types

type Rep OpenChest :: Type -> Type #

Show OpenChest Source # 
Instance details

Defined in Lorentz.Value

Eq OpenChest Source # 
Instance details

Defined in Lorentz.Value

HasAnnotation OpenChest Source # 
Instance details

Defined in Lorentz.Value

TypeHasDoc OpenChest Source # 
Instance details

Defined in Lorentz.Value

Associated Types

type TypeDocFieldDescriptions OpenChest :: FieldDescriptions #

IsoValue OpenChest Source # 
Instance details

Defined in Lorentz.Value

Associated Types

type ToT OpenChest :: T #

type Rep OpenChest Source # 
Instance details

Defined in Lorentz.Value

type Rep OpenChest = D1 ('MetaData "OpenChest" "Lorentz.Value" "lorentz-0.15.0-inplace" 'False) (C1 ('MetaCons "ChestContent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ByteString)) :+: C1 ('MetaCons "ChestOpenFailed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool)))
type TypeDocFieldDescriptions OpenChest Source # 
Instance details

Defined in Lorentz.Value

type ToT OpenChest Source # 
Instance details

Defined in Lorentz.Value

type ToT OpenChest = GValueType (Rep OpenChest)

data EpName #

Instances

Instances details
FromJSON EpName 
Instance details

Defined in Morley.Michelson.Untyped.Entrypoints

ToJSON EpName 
Instance details

Defined in Morley.Michelson.Untyped.Entrypoints

Generic EpName 
Instance details

Defined in Morley.Michelson.Untyped.Entrypoints

Associated Types

type Rep EpName :: Type -> Type #

Methods

from :: EpName -> Rep EpName x #

to :: Rep EpName x -> EpName #

Show EpName 
Instance details

Defined in Morley.Michelson.Untyped.Entrypoints

NFData EpName 
Instance details

Defined in Morley.Michelson.Untyped.Entrypoints

Methods

rnf :: EpName -> () #

Buildable EpName 
Instance details

Defined in Morley.Michelson.Untyped.Entrypoints

Methods

build :: EpName -> Builder #

Eq EpName 
Instance details

Defined in Morley.Michelson.Untyped.Entrypoints

Methods

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

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

Ord EpName 
Instance details

Defined in Morley.Michelson.Untyped.Entrypoints

HasCLReader EpName 
Instance details

Defined in Morley.Michelson.Untyped.Entrypoints

type Rep EpName 
Instance details

Defined in Morley.Michelson.Untyped.Entrypoints

type Rep EpName = D1 ('MetaData "EpName" "Morley.Michelson.Untyped.Entrypoints" "morley-1.19.0-inplace" 'True) (C1 ('MetaCons "UnsafeEpName" 'PrefixI 'True) (S1 ('MetaSel ('Just "unEpName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

pattern DefEpName :: EpName #

type EntrypointCall param arg = EntrypointCallT (ToT param) (ToT arg) #

type SomeEntrypointCall arg = SomeEntrypointCallT (ToT arg) #

Constructors

toMutez :: (Integral a, CheckIntSubType a Word63) => a -> Mutez #

Conversions

callingAddress :: forall cp vd addr mname. (ToTAddress cp vd addr, NiceParameterFull cp) => addr -> EntrypointRef mname -> ContractRef (GetEntrypointArgCustom cp mname) Source #

Turn any typed address 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).

callingDefAddress :: forall cp vd addr. (ToTAddress cp vd addr, NiceParameterFull cp) => addr -> ContractRef (GetDefaultEntrypointArg cp) Source #

Specialization of callingAddress 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 L1Address Source # 
Instance details

Defined in Lorentz.Address

Methods

toAddress :: L1Address -> Address Source #

ToAddress (FutureContract cp) Source # 
Instance details

Defined in Lorentz.Address

ToAddress (ContractRef cp) Source # 
Instance details

Defined in Lorentz.Address

ToAddress (KindedAddress kind) Source # 
Instance details

Defined in Lorentz.Address

Methods

toAddress :: KindedAddress kind -> Address Source #

ToAddress (TAddress cp vd) Source # 
Instance details

Defined in Lorentz.Address

Methods

toAddress :: TAddress cp vd -> Address Source #

class ToTAddress (cp :: Type) (vd :: Type) (a :: Type) where Source #

Convert something referring to a contract (not specific entrypoint) to TAddress in Haskell world.

Methods

toTAddress :: a -> TAddress cp vd Source #

Instances

Instances details
ToTAddress cp vd Address Source # 
Instance details

Defined in Lorentz.Address

Methods

toTAddress :: Address -> TAddress cp vd Source #

ToTAddress cp vd ContractAddress Source # 
Instance details

Defined in Lorentz.Address

Methods

toTAddress :: ContractAddress -> TAddress cp vd Source #

(cp ~ (), vd ~ ()) => ToTAddress cp vd ImplicitAddress Source # 
Instance details

Defined in Lorentz.Address

Methods

toTAddress :: ImplicitAddress -> TAddress cp vd Source #

ToTAddress cp vd L1Address Source # 
Instance details

Defined in Lorentz.Address

Methods

toTAddress :: L1Address -> TAddress cp vd Source #

(cp ~ Txr1CallParam a, vd ~ ()) => ToTAddress cp vd TxRollupAddress Source # 
Instance details

Defined in Lorentz.Txr1Call

Methods

toTAddress :: TxRollupAddress -> TAddress cp vd Source #

(cp ~ cp', vd ~ vd') => ToTAddress cp vd (TAddress cp' vd') Source # 
Instance details

Defined in Lorentz.Address

Methods

toTAddress :: TAddress cp' vd' -> TAddress cp vd 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 vd) Source # 
Instance details

Defined in Lorentz.Address

Methods

toContractRef :: TAddress cp vd -> ContractRef arg Source #

class FromContractRef (cp :: Type) (contract :: Type) where Source #

Convert something from ContractRef in Haskell world.

Methods

fromContractRef :: ContractRef cp -> contract Source #

Instances

Instances details
FromContractRef cp EpAddress Source # 
Instance details

Defined in Lorentz.Address

FromContractRef cp Address Source # 
Instance details

Defined in Lorentz.Address

cp ~ cp' => FromContractRef cp (FutureContract cp') Source # 
Instance details

Defined in Lorentz.Address

cp ~ cp' => FromContractRef cp (ContractRef cp') Source # 
Instance details

Defined in Lorentz.Address

convertContractRef :: forall cp contract2 contract1. (ToContractRef cp contract1, FromContractRef cp contract2) => contract1 -> contract2 Source #

Misc

class Show a #

Conversion of values to readable Strings.

Derived instances of Show have the following properties, which are compatible with derived instances of Read:

  • The result of show is a syntactically correct Haskell expression containing only constants, given the fixity declarations in force at the point where the type is declared. It contains only the constructor names defined in the data type, parentheses, and spaces. When labelled constructor fields are used, braces, commas, field names, and equal signs are also used.
  • If the constructor is defined to be an infix operator, then showsPrec will produce infix applications of the constructor.
  • the representation will be enclosed in parentheses if the precedence of the top-level constructor in x is less than d (associativity is ignored). Thus, if d is 0 then the result is never surrounded in parentheses; if d is 11 it is always surrounded in parentheses, unless it is an atomic expression.
  • If the constructor is defined using record syntax, then show will produce the record-syntax form, with the fields given in the same order as the original declaration.

For example, given the declarations

infixr 5 :^:
data Tree a =  Leaf a  |  Tree a :^: Tree a

the derived instance of Show is equivalent to

instance (Show a) => Show (Tree a) where

       showsPrec d (Leaf m) = showParen (d > app_prec) $
            showString "Leaf " . showsPrec (app_prec+1) m
         where app_prec = 10

       showsPrec d (u :^: v) = showParen (d > up_prec) $
            showsPrec (up_prec+1) u .
            showString " :^: "      .
            showsPrec (up_prec+1) v
         where up_prec = 5

Note that right-associativity of :^: is ignored. For example,

  • show (Leaf 1 :^: Leaf 2 :^: Leaf 3) produces the string "Leaf 1 :^: (Leaf 2 :^: Leaf 3)".

Minimal complete definition

showsPrec | show

Instances

Instances details
Show CabalSpecVersion 
Instance details

Defined in Distribution.CabalSpecVersion

Show HasCommonStanzas 
Instance details

Defined in Distribution.CabalSpecVersion

Show HasElif 
Instance details

Defined in Distribution.CabalSpecVersion

Show PError 
Instance details

Defined in Distribution.Parsec.Error

Show Position 
Instance details

Defined in Distribution.Parsec.Position

Show PWarnType 
Instance details

Defined in Distribution.Parsec.Warning

Show PWarning 
Instance details

Defined in Distribution.Parsec.Warning

Show Structure 
Instance details

Defined in Distribution.Utils.Structured

Show Extension 
Instance details

Defined in Language.Haskell.Extension

Show KnownExtension 
Instance details

Defined in Language.Haskell.Extension

Show Language 
Instance details

Defined in Language.Haskell.Extension

Show Key 
Instance details

Defined in Data.Aeson.Key

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

Show DotNetTime 
Instance details

Defined in Data.Aeson.Types.Internal

Show JSONPathElement 
Instance details

Defined in Data.Aeson.Types.Internal

Show Options 
Instance details

Defined in Data.Aeson.Types.Internal

Show SumEncoding 
Instance details

Defined in Data.Aeson.Types.Internal

Show Value

Since version 1.5.6.0 version object values are printed in lexicographic key order

>>> toJSON $ H.fromList [("a", True), ("z", False)]
Object (fromList [("a",Bool True),("z",Bool False)])
>>> toJSON $ H.fromList [("z", False), ("a", True)]
Object (fromList [("a",Bool True),("z",Bool False)])
Instance details

Defined in Data.Aeson.Types.Internal

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

Show More 
Instance details

Defined in Data.Attoparsec.Internal.Types

Methods

showsPrec :: Int -> More -> ShowS #

show :: More -> String #

showList :: [More] -> ShowS #

Show Pos 
Instance details

Defined in Data.Attoparsec.Internal.Types

Methods

showsPrec :: Int -> Pos -> ShowS #

show :: Pos -> String #

showList :: [Pos] -> ShowS #

Show Constr

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Show ConstrRep

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Show DataRep

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Show DataType

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Show Fixity

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Show All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

showsPrec :: Int -> All -> ShowS #

show :: All -> String #

showList :: [All] -> ShowS #

Show Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

showsPrec :: Int -> Any -> ShowS #

show :: Any -> String #

showList :: [Any] -> ShowS #

Show SomeTypeRep

Since: base-4.10.0.0

Instance details

Defined in Data.Typeable.Internal

Show Version

Since: base-2.1

Instance details

Defined in Data.Version

Show Void

Since: base-4.8.0.0

Instance details

Defined in Data.Void

Methods

showsPrec :: Int -> Void -> ShowS #

show :: Void -> String #

showList :: [Void] -> ShowS #

Show CBool 
Instance details

Defined in Foreign.C.Types

Methods

showsPrec :: Int -> CBool -> ShowS #

show :: CBool -> String #

showList :: [CBool] -> ShowS #

Show CChar 
Instance details

Defined in Foreign.C.Types

Methods

showsPrec :: Int -> CChar -> ShowS #

show :: CChar -> String #

showList :: [CChar] -> ShowS #

Show CClock 
Instance details

Defined in Foreign.C.Types

Show CDouble 
Instance details

Defined in Foreign.C.Types

Show CFloat 
Instance details

Defined in Foreign.C.Types

Show CInt 
Instance details

Defined in Foreign.C.Types

Methods

showsPrec :: Int -> CInt -> ShowS #

show :: CInt -> String #

showList :: [CInt] -> ShowS #

Show CIntMax 
Instance details

Defined in Foreign.C.Types

Show CIntPtr 
Instance details

Defined in Foreign.C.Types

Show CLLong 
Instance details

Defined in Foreign.C.Types

Show CLong 
Instance details

Defined in Foreign.C.Types

Methods

showsPrec :: Int -> CLong -> ShowS #

show :: CLong -> String #

showList :: [CLong] -> ShowS #

Show CPtrdiff 
Instance details

Defined in Foreign.C.Types

Show CSChar 
Instance details

Defined in Foreign.C.Types

Show CSUSeconds 
Instance details

Defined in Foreign.C.Types

Show CShort 
Instance details

Defined in Foreign.C.Types

Show CSigAtomic 
Instance details

Defined in Foreign.C.Types

Show CSize 
Instance details

Defined in Foreign.C.Types

Methods

showsPrec :: Int -> CSize -> ShowS #

show :: CSize -> String #

showList :: [CSize] -> ShowS #

Show CTime 
Instance details

Defined in Foreign.C.Types

Methods

showsPrec :: Int -> CTime -> ShowS #

show :: CTime -> String #

showList :: [CTime] -> ShowS #

Show CUChar 
Instance details

Defined in Foreign.C.Types

Show CUInt 
Instance details

Defined in Foreign.C.Types

Methods

showsPrec :: Int -> CUInt -> ShowS #

show :: CUInt -> String #

showList :: [CUInt] -> ShowS #

Show CUIntMax 
Instance details

Defined in Foreign.C.Types

Show CUIntPtr 
Instance details

Defined in Foreign.C.Types

Show CULLong 
Instance details

Defined in Foreign.C.Types

Show CULong 
Instance details

Defined in Foreign.C.Types

Show CUSeconds 
Instance details

Defined in Foreign.C.Types

Show CUShort 
Instance details

Defined in Foreign.C.Types

Show CWchar 
Instance details

Defined in Foreign.C.Types

Show IntPtr 
Instance details

Defined in Foreign.Ptr

Show WordPtr 
Instance details

Defined in Foreign.Ptr

Show BlockReason

Since: base-4.3.0.0

Instance details

Defined in GHC.Conc.Sync

Show ThreadId

Since: base-4.2.0.0

Instance details

Defined in GHC.Conc.Sync

Show ThreadStatus

Since: base-4.3.0.0

Instance details

Defined in GHC.Conc.Sync

Show ErrorCall

Since: base-4.0.0.0

Instance details

Defined in GHC.Exception

Show ArithException

Since: base-4.0.0.0

Instance details

Defined in GHC.Exception.Type

Show SomeException

Since: base-3.0

Instance details

Defined in GHC.Exception.Type

Show Fingerprint

Since: base-4.7.0.0

Instance details

Defined in GHC.Fingerprint.Type

Show Associativity

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Show DecidedStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Show Fixity

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Show SourceStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Show SourceUnpackedness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Show MaskingState

Since: base-4.3.0.0

Instance details

Defined in GHC.IO

Show AllocationLimitExceeded

Since: base-4.7.1.0

Instance details

Defined in GHC.IO.Exception

Show ArrayException

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show AssertionFailed

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show AsyncException

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show BlockedIndefinitelyOnMVar

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show BlockedIndefinitelyOnSTM

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show CompactionFailed

Since: base-4.10.0.0

Instance details

Defined in GHC.IO.Exception

Show Deadlock

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show ExitCode 
Instance details

Defined in GHC.IO.Exception

Show FixIOException

Since: base-4.11.0.0

Instance details

Defined in GHC.IO.Exception

Show IOErrorType

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show IOException

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show SomeAsyncException

Since: base-4.7.0.0

Instance details

Defined in GHC.IO.Exception

Show BufferMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.Handle.Types

Show Handle

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Handle.Types

Show HandleType

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Handle.Types

Show Newline

Since: base-4.3.0.0

Instance details

Defined in GHC.IO.Handle.Types

Show NewlineMode

Since: base-4.3.0.0

Instance details

Defined in GHC.IO.Handle.Types

Show IOMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.IOMode

Show Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

showsPrec :: Int -> Int16 -> ShowS #

show :: Int16 -> String #

showList :: [Int16] -> ShowS #

Show Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

showsPrec :: Int -> Int32 -> ShowS #

show :: Int32 -> String #

showList :: [Int32] -> ShowS #

Show Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

showsPrec :: Int -> Int64 -> ShowS #

show :: Int64 -> String #

showList :: [Int64] -> ShowS #

Show Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

showsPrec :: Int -> Int8 -> ShowS #

show :: Int8 -> String #

showList :: [Int8] -> ShowS #

Show CCFlags

Since: base-4.8.0.0

Instance details

Defined in GHC.RTS.Flags

Show ConcFlags

Since: base-4.8.0.0

Instance details

Defined in GHC.RTS.Flags

Show DebugFlags

Since: base-4.8.0.0

Instance details

Defined in GHC.RTS.Flags

Show DoCostCentres

Since: base-4.8.0.0

Instance details

Defined in GHC.RTS.Flags

Show DoHeapProfile

Since: base-4.8.0.0

Instance details

Defined in GHC.RTS.Flags

Show DoTrace

Since: base-4.8.0.0

Instance details

Defined in GHC.RTS.Flags

Show GCFlags

Since: base-4.8.0.0

Instance details

Defined in GHC.RTS.Flags

Show GiveGCStats

Since: base-4.8.0.0

Instance details

Defined in GHC.RTS.Flags

Show IoSubSystem 
Instance details

Defined in GHC.RTS.Flags

Show MiscFlags

Since: base-4.8.0.0

Instance details

Defined in GHC.RTS.Flags

Show ParFlags

Since: base-4.8.0.0

Instance details

Defined in GHC.RTS.Flags

Show ProfFlags

Since: base-4.8.0.0

Instance details

Defined in GHC.RTS.Flags

Show RTSFlags

Since: base-4.8.0.0

Instance details

Defined in GHC.RTS.Flags

Show TickyFlags

Since: base-4.8.0.0

Instance details

Defined in GHC.RTS.Flags

Show TraceFlags

Since: base-4.8.0.0

Instance details

Defined in GHC.RTS.Flags

Show CallStack

Since: base-4.9.0.0

Instance details

Defined in GHC.Show

Show SrcLoc

Since: base-4.9.0.0

Instance details

Defined in GHC.Show

Show GCDetails

Since: base-4.10.0.0

Instance details

Defined in GHC.Stats

Show RTSStats

Since: base-4.10.0.0

Instance details

Defined in GHC.Stats

Show SomeSymbol

Since: base-4.7.0.0

Instance details

Defined in GHC.TypeLits

Show SomeNat

Since: base-4.7.0.0

Instance details

Defined in GHC.TypeNats

Show GeneralCategory

Since: base-2.1

Instance details

Defined in GHC.Unicode

Show Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Show Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Show Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Show Lexeme

Since: base-2.1

Instance details

Defined in Text.Read.Lex

Show Number

Since: base-4.6.0.0

Instance details

Defined in Text.Read.Lex

Show Alphabet 
Instance details

Defined in Data.ByteString.Base58.Internal

Show Encoding 
Instance details

Defined in Basement.String

Show ASCII7_Invalid 
Instance details

Defined in Basement.String.Encoding.ASCII7

Methods

showsPrec :: Int -> ASCII7_Invalid -> ShowS #

show :: ASCII7_Invalid -> String #

showList :: [ASCII7_Invalid] -> ShowS #

Show ISO_8859_1_Invalid 
Instance details

Defined in Basement.String.Encoding.ISO_8859_1

Methods

showsPrec :: Int -> ISO_8859_1_Invalid -> ShowS #

show :: ISO_8859_1_Invalid -> String #

showList :: [ISO_8859_1_Invalid] -> ShowS #

Show UTF16_Invalid 
Instance details

Defined in Basement.String.Encoding.UTF16

Methods

showsPrec :: Int -> UTF16_Invalid -> ShowS #

show :: UTF16_Invalid -> String #

showList :: [UTF16_Invalid] -> ShowS #

Show UTF32_Invalid 
Instance details

Defined in Basement.String.Encoding.UTF32

Methods

showsPrec :: Int -> UTF32_Invalid -> ShowS #

show :: UTF32_Invalid -> String #

showList :: [UTF32_Invalid] -> ShowS #

Show AsciiString 
Instance details

Defined in Basement.Types.AsciiString

Show Char7 
Instance details

Defined in Basement.Types.Char7

Methods

showsPrec :: Int -> Char7 -> ShowS #

show :: Char7 -> String #

showList :: [Char7] -> ShowS #

Show FileSize 
Instance details

Defined in Basement.Types.OffsetSize

Show String 
Instance details

Defined in Basement.UTF8.Base

Show BimapException 
Instance details

Defined in Data.Bimap

Methods

showsPrec :: Int -> BimapException -> ShowS #

show :: BimapException -> String #

showList :: [BimapException] -> ShowS #

Show F2Poly 
Instance details

Defined in Data.Bit.F2Poly

Show Bit 
Instance details

Defined in Data.Bit.Internal

Methods

showsPrec :: Int -> Bit -> ShowS #

show :: Bit -> String #

showList :: [Bit] -> ShowS #

Show WithInternals 
Instance details

Defined in Data.Bit.Internal

Methods

showsPrec :: Int -> WithInternals -> ShowS #

show :: WithInternals -> String #

showList :: [WithInternals] -> ShowS #

Show ByteString 
Instance details

Defined in Data.ByteString.Internal

Show ByteString 
Instance details

Defined in Data.ByteString.Lazy.Internal

Show ShortByteString 
Instance details

Defined in Data.ByteString.Short.Internal

Show Clock 
Instance details

Defined in System.Clock

Methods

showsPrec :: Int -> Clock -> ShowS #

show :: Clock -> String #

showList :: [Clock] -> ShowS #

Show TimeSpec 
Instance details

Defined in System.Clock

Show IntSet 
Instance details

Defined in Data.IntSet.Internal

Show Relation 
Instance details

Defined in Data.IntSet.Internal

Methods

showsPrec :: Int -> Relation -> ShowS #

show :: Relation -> String #

showList :: [Relation] -> ShowS #

Show CryptoError 
Instance details

Defined in Crypto.Error.Types

Show Blake2b_160 
Instance details

Defined in Crypto.Hash.Blake2b

Show Blake2b_224 
Instance details

Defined in Crypto.Hash.Blake2b

Show Blake2b_256 
Instance details

Defined in Crypto.Hash.Blake2b

Show Blake2b_384 
Instance details

Defined in Crypto.Hash.Blake2b

Show Blake2b_512 
Instance details

Defined in Crypto.Hash.Blake2b

Show Blake2bp_512 
Instance details

Defined in Crypto.Hash.Blake2bp

Show Blake2s_160 
Instance details

Defined in Crypto.Hash.Blake2s

Show Blake2s_224 
Instance details

Defined in Crypto.Hash.Blake2s

Show Blake2s_256 
Instance details

Defined in Crypto.Hash.Blake2s

Show Blake2sp_224 
Instance details

Defined in Crypto.Hash.Blake2sp

Show Blake2sp_256 
Instance details

Defined in Crypto.Hash.Blake2sp

Show Keccak_224 
Instance details

Defined in Crypto.Hash.Keccak

Show Keccak_256 
Instance details

Defined in Crypto.Hash.Keccak

Show Keccak_384 
Instance details

Defined in Crypto.Hash.Keccak

Show Keccak_512 
Instance details

Defined in Crypto.Hash.Keccak

Show MD2 
Instance details

Defined in Crypto.Hash.MD2

Methods

showsPrec :: Int -> MD2 -> ShowS #

show :: MD2 -> String #

showList :: [MD2] -> ShowS #

Show MD4 
Instance details

Defined in Crypto.Hash.MD4

Methods

showsPrec :: Int -> MD4 -> ShowS #

show :: MD4 -> String #

showList :: [MD4] -> ShowS #

Show MD5 
Instance details

Defined in Crypto.Hash.MD5

Methods

showsPrec :: Int -> MD5 -> ShowS #

show :: MD5 -> String #

showList :: [MD5] -> ShowS #

Show RIPEMD160 
Instance details

Defined in Crypto.Hash.RIPEMD160

Show SHA1 
Instance details

Defined in Crypto.Hash.SHA1

Methods

showsPrec :: Int -> SHA1 -> ShowS #

show :: SHA1 -> String #

showList :: [SHA1] -> ShowS #

Show SHA224 
Instance details

Defined in Crypto.Hash.SHA224

Show SHA256 
Instance details

Defined in Crypto.Hash.SHA256

Show SHA3_224 
Instance details

Defined in Crypto.Hash.SHA3

Show SHA3_256 
Instance details

Defined in Crypto.Hash.SHA3

Show SHA3_384 
Instance details

Defined in Crypto.Hash.SHA3

Show SHA3_512 
Instance details

Defined in Crypto.Hash.SHA3

Show SHA384 
Instance details

Defined in Crypto.Hash.SHA384

Show SHA512 
Instance details

Defined in Crypto.Hash.SHA512

Show SHA512t_224 
Instance details

Defined in Crypto.Hash.SHA512t

Show SHA512t_256 
Instance details

Defined in Crypto.Hash.SHA512t

Show Skein256_224 
Instance details

Defined in Crypto.Hash.Skein256

Show Skein256_256 
Instance details

Defined in Crypto.Hash.Skein256

Show Skein512_224 
Instance details

Defined in Crypto.Hash.Skein512

Show Skein512_256 
Instance details

Defined in Crypto.Hash.Skein512

Show Skein512_384 
Instance details

Defined in Crypto.Hash.Skein512

Show Skein512_512 
Instance details

Defined in Crypto.Hash.Skein512

Show Tiger 
Instance details

Defined in Crypto.Hash.Tiger

Methods

showsPrec :: Int -> Tiger -> ShowS #

show :: Tiger -> String #

showList :: [Tiger] -> ShowS #

Show Whirlpool 
Instance details

Defined in Crypto.Hash.Whirlpool

Show KeyPair 
Instance details

Defined in Crypto.PubKey.ECC.ECDSA

Show PrivateKey 
Instance details

Defined in Crypto.PubKey.ECC.ECDSA

Show PublicKey 
Instance details

Defined in Crypto.PubKey.ECC.ECDSA

Show Signature 
Instance details

Defined in Crypto.PubKey.ECC.ECDSA

Show PublicKey 
Instance details

Defined in Crypto.PubKey.Ed25519

Show SecretKey 
Instance details

Defined in Crypto.PubKey.Ed25519

Show Signature 
Instance details

Defined in Crypto.PubKey.Ed25519

Show ForeignSrcLang 
Instance details

Defined in GHC.ForeignSrcLang.Type

Show Extension 
Instance details

Defined in GHC.LanguageExtensions.Type

Show KindRep 
Instance details

Defined in GHC.Show

Show Module

Since: base-4.9.0.0

Instance details

Defined in GHC.Show

Show Ordering

Since: base-2.1

Instance details

Defined in GHC.Show

Show TrName

Since: base-4.9.0.0

Instance details

Defined in GHC.Show

Show TyCon

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> TyCon -> ShowS #

show :: TyCon -> String #

showList :: [TyCon] -> ShowS #

Show TypeLitSort

Since: base-4.11.0.0

Instance details

Defined in GHC.Show

Show DefName 
Instance details

Defined in Control.Lens.Internal.FieldTH

Show NRational Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Show Rational Source # 
Instance details

Defined in Lorentz.CustomArith.RationalArith

Show EpCallingStep Source # 
Instance details

Defined in Lorentz.Entrypoints.Core

Show ExtConversionError Source # 
Instance details

Defined in Lorentz.Extensible

Show EntrypointLookupError Source # 
Instance details

Defined in Lorentz.UParam

Show Never Source # 
Instance details

Defined in Lorentz.Value

Methods

showsPrec :: Int -> Never -> ShowS #

show :: Never -> String #

showList :: [Never] -> ShowS #

Show OpenChest Source # 
Instance details

Defined in Lorentz.Value

Show ViewInterfaceMatchError Source # 
Instance details

Defined in Lorentz.ViewBase

Show ZSNil Source # 
Instance details

Defined in Lorentz.Zip

Methods

showsPrec :: Int -> ZSNil -> ShowS #

show :: ZSNil -> String #

showList :: [ZSNil] -> ShowS #

Show InvalidPosException 
Instance details

Defined in Text.Megaparsec.Pos

Show Pos 
Instance details

Defined in Text.Megaparsec.Pos

Methods

showsPrec :: Int -> Pos -> ShowS #

show :: Pos -> String #

showList :: [Pos] -> ShowS #

Show SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Show Annotation 
Instance details

Defined in Morley.Micheline.Expression

Methods

showsPrec :: Int -> Annotation -> ShowS #

show :: Annotation -> String #

showList :: [Annotation] -> ShowS #

Show MichelinePrimitive 
Instance details

Defined in Morley.Micheline.Expression

Methods

showsPrec :: Int -> MichelinePrimitive -> ShowS #

show :: MichelinePrimitive -> String #

showList :: [MichelinePrimitive] -> ShowS #

Show TezosMutez 
Instance details

Defined in Morley.Micheline.Json

Methods

showsPrec :: Int -> TezosMutez -> ShowS #

show :: TezosMutez -> String #

showList :: [TezosMutez] -> ShowS #

Show AnalyzerRes 
Instance details

Defined in Morley.Michelson.Analyzer

Methods

showsPrec :: Int -> AnalyzerRes -> ShowS #

show :: AnalyzerRes -> String #

showList :: [AnalyzerRes] -> ShowS #

Show DocGrouping 
Instance details

Defined in Morley.Michelson.Doc

Show DocItemId 
Instance details

Defined in Morley.Michelson.Doc

Show DocItemPos 
Instance details

Defined in Morley.Michelson.Doc

Show SomeDocItem 
Instance details

Defined in Morley.Michelson.Doc

Show ErrorSrcPos 
Instance details

Defined in Morley.Michelson.ErrorPos

Methods

showsPrec :: Int -> ErrorSrcPos -> ShowS #

show :: ErrorSrcPos -> String #

showList :: [ErrorSrcPos] -> ShowS #

Show Pos 
Instance details

Defined in Morley.Michelson.ErrorPos

Methods

showsPrec :: Int -> Pos -> ShowS #

show :: Pos -> String #

showList :: [Pos] -> ShowS #

Show SrcPos 
Instance details

Defined in Morley.Michelson.ErrorPos

Methods

showsPrec :: Int -> SrcPos -> ShowS #

show :: SrcPos -> String #

showList :: [SrcPos] -> ShowS #

Show InterpretResult 
Instance details

Defined in Morley.Michelson.Interpret

Methods

showsPrec :: Int -> InterpretResult -> ShowS #

show :: InterpretResult -> String #

showList :: [InterpretResult] -> ShowS #

Show InterpreterState 
Instance details

Defined in Morley.Michelson.Interpret

Methods

showsPrec :: Int -> InterpreterState -> ShowS #

show :: InterpreterState -> String #

showList :: [InterpreterState] -> ShowS #

Show MorleyLogs 
Instance details

Defined in Morley.Michelson.Interpret

Methods

showsPrec :: Int -> MorleyLogs -> ShowS #

show :: MorleyLogs -> String #

showList :: [MorleyLogs] -> ShowS #

Show RemainingSteps 
Instance details

Defined in Morley.Michelson.Interpret

Methods

showsPrec :: Int -> RemainingSteps -> ShowS #

show :: RemainingSteps -> String #

showList :: [RemainingSteps] -> ShowS #

Show CadrStruct 
Instance details

Defined in Morley.Michelson.Macro

Methods

showsPrec :: Int -> CadrStruct -> ShowS #

show :: CadrStruct -> String #

showList :: [CadrStruct] -> ShowS #

Show Macro 
Instance details

Defined in Morley.Michelson.Macro

Methods

showsPrec :: Int -> Macro -> ShowS #

show :: Macro -> String #

showList :: [Macro] -> ShowS #

Show PairStruct 
Instance details

Defined in Morley.Michelson.Macro

Methods

showsPrec :: Int -> PairStruct -> ShowS #

show :: PairStruct -> String #

showList :: [PairStruct] -> ShowS #

Show ParsedOp 
Instance details

Defined in Morley.Michelson.Macro

Methods

showsPrec :: Int -> ParsedOp -> ShowS #

show :: ParsedOp -> String #

showList :: [ParsedOp] -> ShowS #

Show UnpairStruct 
Instance details

Defined in Morley.Michelson.Macro

Methods

showsPrec :: Int -> UnpairStruct -> ShowS #

show :: UnpairStruct -> String #

showList :: [UnpairStruct] -> ShowS #

Show CustomParserException 
Instance details

Defined in Morley.Michelson.Parser.Error

Methods

showsPrec :: Int -> CustomParserException -> ShowS #

show :: CustomParserException -> String #

showList :: [CustomParserException] -> ShowS #

Show ParserException 
Instance details

Defined in Morley.Michelson.Parser.Error

Methods

showsPrec :: Int -> ParserException -> ShowS #

show :: ParserException -> String #

showList :: [ParserException] -> ShowS #

Show StringLiteralParserException 
Instance details

Defined in Morley.Michelson.Parser.Error

Methods

showsPrec :: Int -> StringLiteralParserException -> ShowS #

show :: StringLiteralParserException -> String #

showList :: [StringLiteralParserException] -> ShowS #

Show MichelsonSource 
Instance details

Defined in Morley.Michelson.Parser.Types

Methods

showsPrec :: Int -> MichelsonSource -> ShowS #

show :: MichelsonSource -> String #

showList :: [MichelsonSource] -> ShowS #

Show ParserOptions 
Instance details

Defined in Morley.Michelson.Parser.Types

Methods

showsPrec :: Int -> ParserOptions -> ShowS #

show :: ParserOptions -> String #

showList :: [ParserOptions] -> ShowS #

Show BigMapCounter 
Instance details

Defined in Morley.Michelson.Runtime.GState

Methods

showsPrec :: Int -> BigMapCounter -> ShowS #

show :: BigMapCounter -> String #

showList :: [BigMapCounter] -> ShowS #

Show ContractState 
Instance details

Defined in Morley.Michelson.Runtime.GState

Methods

showsPrec :: Int -> ContractState -> ShowS #

show :: ContractState -> String #

showList :: [ContractState] -> ShowS #

Show GState 
Instance details

Defined in Morley.Michelson.Runtime.GState

Methods

showsPrec :: Int -> GState -> ShowS #

show :: GState -> String #

showList :: [GState] -> ShowS #

Show GStateParseError 
Instance details

Defined in Morley.Michelson.Runtime.GState

Methods

showsPrec :: Int -> GStateParseError -> ShowS #

show :: GStateParseError -> String #

showList :: [GStateParseError] -> ShowS #

Show GStateUpdate 
Instance details

Defined in Morley.Michelson.Runtime.GState

Methods

showsPrec :: Int -> GStateUpdate -> ShowS #

show :: GStateUpdate -> String #

showList :: [GStateUpdate] -> ShowS #

Show GStateUpdateError 
Instance details

Defined in Morley.Michelson.Runtime.GState

Methods

showsPrec :: Int -> GStateUpdateError -> ShowS #

show :: GStateUpdateError -> String #

showList :: [GStateUpdateError] -> ShowS #

Show ImplicitState 
Instance details

Defined in Morley.Michelson.Runtime.GState

Methods

showsPrec :: Int -> ImplicitState -> ShowS #

show :: ImplicitState -> String #

showList :: [ImplicitState] -> ShowS #

Show VotingPowers 
Instance details

Defined in Morley.Michelson.Runtime.GState

Methods

showsPrec :: Int -> VotingPowers -> ShowS #

show :: VotingPowers -> String #

showList :: [VotingPowers] -> ShowS #

Show MText 
Instance details

Defined in Morley.Michelson.Text

Methods

showsPrec :: Int -> MText -> ShowS #

show :: MText -> String #

showList :: [MText] -> ShowS #

Show ExtError 
Instance details

Defined in Morley.Michelson.TypeCheck.Error

Methods

showsPrec :: Int -> ExtError -> ShowS #

show :: ExtError -> String #

showList :: [ExtError] -> ShowS #

Show StackSize 
Instance details

Defined in Morley.Michelson.TypeCheck.Error

Methods

showsPrec :: Int -> StackSize -> ShowS #

show :: StackSize -> String #

showList :: [StackSize] -> ShowS #

Show TcTypeError 
Instance details

Defined in Morley.Michelson.TypeCheck.Error

Methods

showsPrec :: Int -> TcTypeError -> ShowS #

show :: TcTypeError -> String #

showList :: [TcTypeError] -> ShowS #

Show TopLevelType 
Instance details

Defined in Morley.Michelson.TypeCheck.Error

Methods

showsPrec :: Int -> TopLevelType -> ShowS #

show :: TopLevelType -> String #

showList :: [TopLevelType] -> ShowS #

Show TypeContext 
Instance details

Defined in Morley.Michelson.TypeCheck.Error

Methods

showsPrec :: Int -> TypeContext -> ShowS #

show :: TypeContext -> String #

showList :: [TypeContext] -> ShowS #

Show SomeParamType 
Instance details

Defined in Morley.Michelson.TypeCheck.TypeCheck

Methods

showsPrec :: Int -> SomeParamType -> ShowS #

show :: SomeParamType -> String #

showList :: [SomeParamType] -> ShowS #

Show SomeHST 
Instance details

Defined in Morley.Michelson.TypeCheck.Types

Methods

showsPrec :: Int -> SomeHST -> ShowS #

show :: SomeHST -> String #

showList :: [SomeHST] -> ShowS #

Show SomeAnnotatedValue 
Instance details

Defined in Morley.Michelson.Typed.AnnotatedValue

Methods

showsPrec :: Int -> SomeAnnotatedValue -> ShowS #

show :: SomeAnnotatedValue -> String #

showList :: [SomeAnnotatedValue] -> ShowS #

Show MutezArithErrorType 
Instance details

Defined in Morley.Michelson.Typed.Arith

Methods

showsPrec :: Int -> MutezArithErrorType -> ShowS #

show :: MutezArithErrorType -> String #

showList :: [MutezArithErrorType] -> ShowS #

Show ShiftArithErrorType 
Instance details

Defined in Morley.Michelson.Typed.Arith

Methods

showsPrec :: Int -> ShiftArithErrorType -> ShowS #

show :: ShiftArithErrorType -> String #

showList :: [ShiftArithErrorType] -> ShowS #

Show FailureType 
Instance details

Defined in Morley.Michelson.Typed.ClassifiedInstr.Internal.Types

Methods

showsPrec :: Int -> FailureType -> ShowS #

show :: FailureType -> String #

showList :: [FailureType] -> ShowS #

Show HasAnns 
Instance details

Defined in Morley.Michelson.Typed.ClassifiedInstr.Internal.Types

Methods

showsPrec :: Int -> HasAnns -> ShowS #

show :: HasAnns -> String #

showList :: [HasAnns] -> ShowS #

Show IsMichelson 
Instance details

Defined in Morley.Michelson.Typed.ClassifiedInstr.Internal.Types

Methods

showsPrec :: Int -> IsMichelson -> ShowS #

show :: IsMichelson -> String #

showList :: [IsMichelson] -> ShowS #

Show NumChildren 
Instance details

Defined in Morley.Michelson.Typed.ClassifiedInstr.Internal.Types

Methods

showsPrec :: Int -> NumChildren -> ShowS #

show :: NumChildren -> String #

showList :: [NumChildren] -> ShowS #

Show UntypingOptions 
Instance details

Defined in Morley.Michelson.Typed.Convert

Methods

showsPrec :: Int -> UntypingOptions -> ShowS #

show :: UntypingOptions -> String #

showList :: [UntypingOptions] -> ShowS #

Show ArmCoord 
Instance details

Defined in Morley.Michelson.Typed.Entrypoints

Methods

showsPrec :: Int -> ArmCoord -> ShowS #

show :: ArmCoord -> String #

showList :: [ArmCoord] -> ShowS #

Show EpAddress 
Instance details

Defined in Morley.Michelson.Typed.Entrypoints

Show ParamEpError 
Instance details

Defined in Morley.Michelson.Typed.Entrypoints

Methods

showsPrec :: Int -> ParamEpError -> ShowS #

show :: ParamEpError -> String #

showList :: [ParamEpError] -> ShowS #

Show ParseEpAddressError 
Instance details

Defined in Morley.Michelson.Typed.Entrypoints

Methods

showsPrec :: Int -> ParseEpAddressError -> ShowS #

show :: ParseEpAddressError -> String #

showList :: [ParseEpAddressError] -> ShowS #

Show SomeContract 
Instance details

Defined in Morley.Michelson.Typed.Existential

Methods

showsPrec :: Int -> SomeContract -> ShowS #

show :: SomeContract -> String #

showList :: [SomeContract] -> ShowS #

Show SomeContractAndStorage 
Instance details

Defined in Morley.Michelson.Typed.Existential

Methods

showsPrec :: Int -> SomeContractAndStorage -> ShowS #

show :: SomeContractAndStorage -> String #

showList :: [SomeContractAndStorage] -> ShowS #

Show CommentType 
Instance details

Defined in Morley.Michelson.Typed.Instr

Methods

showsPrec :: Int -> CommentType -> ShowS #

show :: CommentType -> String #

showList :: [CommentType] -> ShowS #

Show SomeMeta 
Instance details

Defined in Morley.Michelson.Typed.Instr

Methods

showsPrec :: Int -> SomeMeta -> ShowS #

show :: SomeMeta -> String #

showList :: [SomeMeta] -> ShowS #

Show EmitOperation 
Instance details

Defined in Morley.Michelson.Typed.Operation

Methods

showsPrec :: Int -> EmitOperation -> ShowS #

show :: EmitOperation -> String #

showList :: [EmitOperation] -> ShowS #

Show OperationHash 
Instance details

Defined in Morley.Michelson.Typed.Operation

Methods

showsPrec :: Int -> OperationHash -> ShowS #

show :: OperationHash -> String #

showList :: [OperationHash] -> ShowS #

Show OriginationOperation 
Instance details

Defined in Morley.Michelson.Typed.Operation

Methods

showsPrec :: Int -> OriginationOperation -> ShowS #

show :: OriginationOperation -> String #

showList :: [OriginationOperation] -> ShowS #

Show SetDelegateOperation 
Instance details

Defined in Morley.Michelson.Typed.Operation

Methods

showsPrec :: Int -> SetDelegateOperation -> ShowS #

show :: SetDelegateOperation -> String #

showList :: [SetDelegateOperation] -> ShowS #

Show TransferOperation 
Instance details

Defined in Morley.Michelson.Typed.Operation

Methods

showsPrec :: Int -> TransferOperation -> ShowS #

show :: TransferOperation -> String #

showList :: [TransferOperation] -> ShowS #

Show BadTypeForScope 
Instance details

Defined in Morley.Michelson.Typed.Scope

Methods

showsPrec :: Int -> BadTypeForScope -> ShowS #

show :: BadTypeForScope -> String #

showList :: [BadTypeForScope] -> ShowS #

Show T 
Instance details

Defined in Morley.Michelson.Typed.T

Methods

showsPrec :: Int -> T -> ShowS #

show :: T -> String #

showList :: [T] -> ShowS #

Show SetDelegate 
Instance details

Defined in Morley.Michelson.Typed.Value

Methods

showsPrec :: Int -> SetDelegate -> ShowS #

show :: SetDelegate -> String #

showList :: [SetDelegate] -> ShowS #

Show ViewsSetError 
Instance details

Defined in Morley.Michelson.Typed.View

Methods

showsPrec :: Int -> ViewsSetError -> ShowS #

show :: ViewsSetError -> String #

showList :: [ViewsSetError] -> ShowS #

Show AnnotationSet 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

Methods

showsPrec :: Int -> AnnotationSet -> ShowS #

show :: AnnotationSet -> String #

showList :: [AnnotationSet] -> ShowS #

Show AnyAnn 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

Methods

showsPrec :: Int -> AnyAnn -> ShowS #

show :: AnyAnn -> String #

showList :: [AnyAnn] -> ShowS #

Show VarAnns 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

Methods

showsPrec :: Int -> VarAnns -> ShowS #

show :: VarAnns -> String #

showList :: [VarAnns] -> ShowS #

Show EntriesOrder 
Instance details

Defined in Morley.Michelson.Untyped.Contract

Methods

showsPrec :: Int -> EntriesOrder -> ShowS #

show :: EntriesOrder -> String #

showList :: [EntriesOrder] -> ShowS #

Show EpName 
Instance details

Defined in Morley.Michelson.Untyped.Entrypoints

Show EpNameFromRefAnnError 
Instance details

Defined in Morley.Michelson.Untyped.Entrypoints

Methods

showsPrec :: Int -> EpNameFromRefAnnError -> ShowS #

show :: EpNameFromRefAnnError -> String #

showList :: [EpNameFromRefAnnError] -> ShowS #

Show HandleImplicitDefaultEp 
Instance details

Defined in Morley.Michelson.Untyped.Entrypoints

Methods

showsPrec :: Int -> HandleImplicitDefaultEp -> ShowS #

show :: HandleImplicitDefaultEp -> String #

showList :: [HandleImplicitDefaultEp] -> ShowS #

Show PrintComment 
Instance details

Defined in Morley.Michelson.Untyped.Ext

Methods

showsPrec :: Int -> PrintComment -> ShowS #

show :: PrintComment -> String #

showList :: [PrintComment] -> ShowS #

Show StackRef 
Instance details

Defined in Morley.Michelson.Untyped.Ext

Methods

showsPrec :: Int -> StackRef -> ShowS #

show :: StackRef -> String #

showList :: [StackRef] -> ShowS #

Show StackTypePattern 
Instance details

Defined in Morley.Michelson.Untyped.Ext

Methods

showsPrec :: Int -> StackTypePattern -> ShowS #

show :: StackTypePattern -> String #

showList :: [StackTypePattern] -> ShowS #

Show TyVar 
Instance details

Defined in Morley.Michelson.Untyped.Ext

Methods

showsPrec :: Int -> TyVar -> ShowS #

show :: TyVar -> String #

showList :: [TyVar] -> ShowS #

Show Var 
Instance details

Defined in Morley.Michelson.Untyped.Ext

Methods

showsPrec :: Int -> Var -> ShowS #

show :: Var -> String #

showList :: [Var] -> ShowS #

Show ExpandedOp 
Instance details

Defined in Morley.Michelson.Untyped.Instr

Methods

showsPrec :: Int -> ExpandedOp -> ShowS #

show :: ExpandedOp -> String #

showList :: [ExpandedOp] -> ShowS #

Show ParameterType 
Instance details

Defined in Morley.Michelson.Untyped.Type

Methods

showsPrec :: Int -> ParameterType -> ShowS #

show :: ParameterType -> String #

showList :: [ParameterType] -> ShowS #

Show T 
Instance details

Defined in Morley.Michelson.Untyped.Type

Methods

showsPrec :: Int -> T -> ShowS #

show :: T -> String #

showList :: [T] -> ShowS #

Show Ty 
Instance details

Defined in Morley.Michelson.Untyped.Type

Methods

showsPrec :: Int -> Ty -> ShowS #

show :: Ty -> String #

showList :: [Ty] -> ShowS #

Show InternalByteString 
Instance details

Defined in Morley.Michelson.Untyped.Value

Methods

showsPrec :: Int -> InternalByteString -> ShowS #

show :: InternalByteString -> String #

showList :: [InternalByteString] -> ShowS #

Show BadViewNameError 
Instance details

Defined in Morley.Michelson.Untyped.View

Methods

showsPrec :: Int -> BadViewNameError -> ShowS #

show :: BadViewNameError -> String #

showList :: [BadViewNameError] -> ShowS #

Show ViewName 
Instance details

Defined in Morley.Michelson.Untyped.View

Show AnyParsableAddress 
Instance details

Defined in Morley.Tezos.Address

Methods

showsPrec :: Int -> AnyParsableAddress -> ShowS #

show :: AnyParsableAddress -> String #

showList :: [AnyParsableAddress] -> ShowS #

Show GlobalCounter 
Instance details

Defined in Morley.Tezos.Address

Methods

showsPrec :: Int -> GlobalCounter -> ShowS #

show :: GlobalCounter -> String #

showList :: [GlobalCounter] -> ShowS #

Show ParseAddressError 
Instance details

Defined in Morley.Tezos.Address

Methods

showsPrec :: Int -> ParseAddressError -> ShowS #

show :: ParseAddressError -> String #

showList :: [ParseAddressError] -> ShowS #

Show ParseAddressRawError 
Instance details

Defined in Morley.Tezos.Address

Methods

showsPrec :: Int -> ParseAddressRawError -> ShowS #

show :: ParseAddressRawError -> String #

showList :: [ParseAddressRawError] -> ShowS #

Show TxRollupL2Address 
Instance details

Defined in Morley.Tezos.Address

Methods

showsPrec :: Int -> TxRollupL2Address -> ShowS #

show :: TxRollupL2Address -> String #

showList :: [TxRollupL2Address] -> ShowS #

Show SomeAddressOrAlias 
Instance details

Defined in Morley.Tezos.Address.Alias

Methods

showsPrec :: Int -> SomeAddressOrAlias -> ShowS #

show :: SomeAddressOrAlias -> String #

showList :: [SomeAddressOrAlias] -> ShowS #

Show AddressKind 
Instance details

Defined in Morley.Tezos.Address.Kinds

Methods

showsPrec :: Int -> AddressKind -> ShowS #

show :: AddressKind -> String #

showList :: [AddressKind] -> ShowS #

Show ChainId 
Instance details

Defined in Morley.Tezos.Core

Show Mutez 
Instance details

Defined in Morley.Tezos.Core

Methods

showsPrec :: Int -> Mutez -> ShowS #

show :: Mutez -> String #

showList :: [Mutez] -> ShowS #

Show ParseChainIdError 
Instance details

Defined in Morley.Tezos.Core

Methods

showsPrec :: Int -> ParseChainIdError -> ShowS #

show :: ParseChainIdError -> String #

showList :: [ParseChainIdError] -> ShowS #

Show Timestamp 
Instance details

Defined in Morley.Tezos.Core

Show KeyType 
Instance details

Defined in Morley.Tezos.Crypto

Methods

showsPrec :: Int -> KeyType -> ShowS #

show :: KeyType -> String #

showList :: [KeyType] -> ShowS #

Show ParseSignatureRawError 
Instance details

Defined in Morley.Tezos.Crypto

Methods

showsPrec :: Int -> ParseSignatureRawError -> ShowS #

show :: ParseSignatureRawError -> String #

showList :: [ParseSignatureRawError] -> ShowS #

Show PublicKey 
Instance details

Defined in Morley.Tezos.Crypto

Show SecretKey 
Instance details

Defined in Morley.Tezos.Crypto

Methods

showsPrec :: Int -> SecretKey -> ShowS #

show :: SecretKey -> String #

showList :: [SecretKey] -> ShowS #

Show Signature 
Instance details

Defined in Morley.Tezos.Crypto

Show Bls12381Fr 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

Show Bls12381G1 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

Show Bls12381G2 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

Show DeserializationError 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

Methods

showsPrec :: Int -> DeserializationError -> ShowS #

show :: DeserializationError -> String #

showList :: [DeserializationError] -> ShowS #

Show PublicKey 
Instance details

Defined in Morley.Tezos.Crypto.Ed25519

Methods

showsPrec :: Int -> PublicKey -> ShowS #

show :: PublicKey -> String #

showList :: [PublicKey] -> ShowS #

Show SecretKey 
Instance details

Defined in Morley.Tezos.Crypto.Ed25519

Methods

showsPrec :: Int -> SecretKey -> ShowS #

show :: SecretKey -> String #

showList :: [SecretKey] -> ShowS #

Show Signature 
Instance details

Defined in Morley.Tezos.Crypto.Ed25519

Methods

showsPrec :: Int -> Signature -> ShowS #

show :: Signature -> String #

showList :: [Signature] -> ShowS #

Show PublicKey 
Instance details

Defined in Morley.Tezos.Crypto.P256

Methods

showsPrec :: Int -> PublicKey -> ShowS #

show :: PublicKey -> String #

showList :: [PublicKey] -> ShowS #

Show SecretKey 
Instance details

Defined in Morley.Tezos.Crypto.P256

Methods

showsPrec :: Int -> SecretKey -> ShowS #

show :: SecretKey -> String #

showList :: [SecretKey] -> ShowS #

Show Signature 
Instance details

Defined in Morley.Tezos.Crypto.P256

Methods

showsPrec :: Int -> Signature -> ShowS #

show :: Signature -> String #

showList :: [Signature] -> ShowS #

Show PublicKey 
Instance details

Defined in Morley.Tezos.Crypto.Secp256k1

Methods

showsPrec :: Int -> PublicKey -> ShowS #

show :: PublicKey -> String #

showList :: [PublicKey] -> ShowS #

Show SecretKey 
Instance details

Defined in Morley.Tezos.Crypto.Secp256k1

Methods

showsPrec :: Int -> SecretKey -> ShowS #

show :: SecretKey -> String #

showList :: [SecretKey] -> ShowS #

Show Signature 
Instance details

Defined in Morley.Tezos.Crypto.Secp256k1

Methods

showsPrec :: Int -> Signature -> ShowS #

show :: Signature -> String #

showList :: [Signature] -> ShowS #

Show Chest 
Instance details

Defined in Morley.Tezos.Crypto.Timelock

Methods

showsPrec :: Int -> Chest -> ShowS #

show :: Chest -> String #

showList :: [Chest] -> ShowS #

Show ChestKey 
Instance details

Defined in Morley.Tezos.Crypto.Timelock

Show Ciphertext 
Instance details

Defined in Morley.Tezos.Crypto.Timelock

Methods

showsPrec :: Int -> Ciphertext -> ShowS #

show :: Ciphertext -> String #

showList :: [Ciphertext] -> ShowS #

Show Locked 
Instance details

Defined in Morley.Tezos.Crypto.Timelock

Methods

showsPrec :: Int -> Locked -> ShowS #

show :: Locked -> String #

showList :: [Locked] -> ShowS #

Show Nonce 
Instance details

Defined in Morley.Tezos.Crypto.Timelock

Methods

showsPrec :: Int -> Nonce -> ShowS #

show :: Nonce -> String #

showList :: [Nonce] -> ShowS #

Show OpeningResult 
Instance details

Defined in Morley.Tezos.Crypto.Timelock

Methods

showsPrec :: Int -> OpeningResult -> ShowS #

show :: OpeningResult -> String #

showList :: [OpeningResult] -> ShowS #

Show Proof 
Instance details

Defined in Morley.Tezos.Crypto.Timelock

Methods

showsPrec :: Int -> Proof -> ShowS #

show :: Proof -> String #

showList :: [Proof] -> ShowS #

Show PublicModulus 
Instance details

Defined in Morley.Tezos.Crypto.Timelock

Methods

showsPrec :: Int -> PublicModulus -> ShowS #

show :: PublicModulus -> String #

showList :: [PublicModulus] -> ShowS #

Show RSAFactors 
Instance details

Defined in Morley.Tezos.Crypto.Timelock

Methods

showsPrec :: Int -> RSAFactors -> ShowS #

show :: RSAFactors -> String #

showList :: [RSAFactors] -> ShowS #

Show SymmetricKey 
Instance details

Defined in Morley.Tezos.Crypto.Timelock

Methods

showsPrec :: Int -> SymmetricKey -> ShowS #

show :: SymmetricKey -> String #

showList :: [SymmetricKey] -> ShowS #

Show TLTime 
Instance details

Defined in Morley.Tezos.Crypto.Timelock

Methods

showsPrec :: Int -> TLTime -> ShowS #

show :: TLTime -> String #

showList :: [TLTime] -> ShowS #

Show Unlocked 
Instance details

Defined in Morley.Tezos.Crypto.Timelock

Methods

showsPrec :: Int -> Unlocked -> ShowS #

show :: Unlocked -> String #

showList :: [Unlocked] -> ShowS #

Show B58CheckWithPrefixError 
Instance details

Defined in Morley.Tezos.Crypto.Util

Methods

showsPrec :: Int -> B58CheckWithPrefixError -> ShowS #

show :: B58CheckWithPrefixError -> String #

showList :: [B58CheckWithPrefixError] -> ShowS #

Show CryptoParseError 
Instance details

Defined in Morley.Tezos.Crypto.Util

Methods

showsPrec :: Int -> CryptoParseError -> ShowS #

show :: CryptoParseError -> String #

showList :: [CryptoParseError] -> ShowS #

Show UnpackError 
Instance details

Defined in Morley.Util.Binary

Methods

showsPrec :: Int -> UnpackError -> ShowS #

show :: UnpackError -> String #

showList :: [UnpackError] -> ShowS #

Show HexJSONByteString 
Instance details

Defined in Morley.Util.ByteString

Methods

showsPrec :: Int -> HexJSONByteString -> ShowS #

show :: HexJSONByteString -> String #

showList :: [HexJSONByteString] -> ShowS #

Show AltNodeType 
Instance details

Defined in Options.Applicative.Types

Show ArgPolicy 
Instance details

Defined in Options.Applicative.Types

Show ArgumentReachability 
Instance details

Defined in Options.Applicative.Types

Show Backtracking 
Instance details

Defined in Options.Applicative.Types

Show CompletionResult 
Instance details

Defined in Options.Applicative.Types

Show IsCmdStart 
Instance details

Defined in Options.Applicative.Types

Show OptName 
Instance details

Defined in Options.Applicative.Types

Show OptProperties 
Instance details

Defined in Options.Applicative.Types

Show OptVisibility 
Instance details

Defined in Options.Applicative.Types

Show ParserPrefs 
Instance details

Defined in Options.Applicative.Types

Show Mode 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

showsPrec :: Int -> Mode -> ShowS #

show :: Mode -> String #

showList :: [Mode] -> ShowS #

Show Style 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

showsPrec :: Int -> Style -> ShowS #

show :: Style -> String #

showList :: [Style] -> ShowS #

Show TextDetails 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Show Doc 
Instance details

Defined in Text.PrettyPrint.HughesPJ

Methods

showsPrec :: Int -> Doc -> ShowS #

show :: Doc -> String #

showList :: [Doc] -> ShowS #

Show ByteArray

Behavior changed in 0.7.2.0. Before 0.7.2.0, this instance rendered 8-bit words less than 16 as a single hexadecimal digit (e.g. 13 was 0xD). Starting with 0.7.2.0, all 8-bit words are represented as two digits (e.g. 13 is 0x0D).

Since: primitive-0.6.3.0

Instance details

Defined in Data.Primitive.ByteArray

Show StdGen 
Instance details

Defined in System.Random.Internal

Show Scientific

See formatScientific if you need more control over the rendering.

Instance details

Defined in Data.Scientific

Show Mod2 
Instance details

Defined in Data.Semiring

Methods

showsPrec :: Int -> Mod2 -> ShowS #

show :: Mod2 -> String #

showList :: [Mod2] -> ShowS #

Show DependencyType 
Instance details

Defined in Test.Tasty.Core

Show FailureReason 
Instance details

Defined in Test.Tasty.Core

Show Outcome 
Instance details

Defined in Test.Tasty.Core

Show Progress 
Instance details

Defined in Test.Tasty.Core

Show ResourceError 
Instance details

Defined in Test.Tasty.Core

Methods

showsPrec :: Int -> ResourceError -> ShowS #

show :: ResourceError -> String #

showList :: [ResourceError] -> ShowS #

Show Result 
Instance details

Defined in Test.Tasty.Core

Show Expr 
Instance details

Defined in Test.Tasty.Patterns.Types

Methods

showsPrec :: Int -> Expr -> ShowS #

show :: Expr -> String #

showList :: [Expr] -> ShowS #

Show Doc 
Instance details

Defined in Language.Haskell.TH.PprLib

Methods

showsPrec :: Int -> Doc -> ShowS #

show :: Doc -> String #

showList :: [Doc] -> ShowS #

Show AnnLookup 
Instance details

Defined in Language.Haskell.TH.Syntax

Show AnnTarget 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Bang 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Bang -> ShowS #

show :: Bang -> String #

showList :: [Bang] -> ShowS #

Show Body 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Body -> ShowS #

show :: Body -> String #

showList :: [Body] -> ShowS #

Show Bytes 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Bytes -> ShowS #

show :: Bytes -> String #

showList :: [Bytes] -> ShowS #

Show Callconv 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Clause 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Con 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Con -> ShowS #

show :: Con -> String #

showList :: [Con] -> ShowS #

Show Dec 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Dec -> ShowS #

show :: Dec -> String #

showList :: [Dec] -> ShowS #

Show DecidedStrictness 
Instance details

Defined in Language.Haskell.TH.Syntax

Show DerivClause 
Instance details

Defined in Language.Haskell.TH.Syntax

Show DerivStrategy 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Exp 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Exp -> ShowS #

show :: Exp -> String #

showList :: [Exp] -> ShowS #

Show FamilyResultSig 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Fixity 
Instance details

Defined in Language.Haskell.TH.Syntax

Show FixityDirection 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Foreign 
Instance details

Defined in Language.Haskell.TH.Syntax

Show FunDep 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Guard 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Guard -> ShowS #

show :: Guard -> String #

showList :: [Guard] -> ShowS #

Show Info 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Info -> ShowS #

show :: Info -> String #

showList :: [Info] -> ShowS #

Show InjectivityAnn 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Inline 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Lit 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Lit -> ShowS #

show :: Lit -> String #

showList :: [Lit] -> ShowS #

Show Loc 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Loc -> ShowS #

show :: Loc -> String #

showList :: [Loc] -> ShowS #

Show Match 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Match -> ShowS #

show :: Match -> String #

showList :: [Match] -> ShowS #

Show ModName 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Module 
Instance details

Defined in Language.Haskell.TH.Syntax

Show ModuleInfo 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Name 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

Show NameFlavour 
Instance details

Defined in Language.Haskell.TH.Syntax

Show NameSpace 
Instance details

Defined in Language.Haskell.TH.Syntax

Show OccName 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Overlap 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Pat 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Pat -> ShowS #

show :: Pat -> String #

showList :: [Pat] -> ShowS #

Show PatSynArgs 
Instance details

Defined in Language.Haskell.TH.Syntax

Show PatSynDir 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Phases 
Instance details

Defined in Language.Haskell.TH.Syntax

Show PkgName 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Pragma 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Range 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Range -> ShowS #

show :: Range -> String #

showList :: [Range] -> ShowS #

Show Role 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Role -> ShowS #

show :: Role -> String #

showList :: [Role] -> ShowS #

Show RuleBndr 
Instance details

Defined in Language.Haskell.TH.Syntax

Show RuleMatch 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Safety 
Instance details

Defined in Language.Haskell.TH.Syntax

Show SourceStrictness 
Instance details

Defined in Language.Haskell.TH.Syntax

Show SourceUnpackedness 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Specificity 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Stmt 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Stmt -> ShowS #

show :: Stmt -> String #

showList :: [Stmt] -> ShowS #

Show TyLit 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> TyLit -> ShowS #

show :: TyLit -> String #

showList :: [TyLit] -> ShowS #

Show TySynEqn 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Type 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

Show TypeFamilyHead 
Instance details

Defined in Language.Haskell.TH.Syntax

Show UnicodeException 
Instance details

Defined in Data.Text.Encoding.Error

Show Builder 
Instance details

Defined in Data.Text.Internal.Builder

Show ShortText 
Instance details

Defined in Data.Text.Short.Internal

Show ConstructorInfo 
Instance details

Defined in Language.Haskell.TH.Datatype

Show ConstructorVariant 
Instance details

Defined in Language.Haskell.TH.Datatype

Show DatatypeInfo 
Instance details

Defined in Language.Haskell.TH.Datatype

Show DatatypeVariant 
Instance details

Defined in Language.Haskell.TH.Datatype

Show FieldStrictness 
Instance details

Defined in Language.Haskell.TH.Datatype

Show Strictness 
Instance details

Defined in Language.Haskell.TH.Datatype

Show Unpackedness 
Instance details

Defined in Language.Haskell.TH.Datatype

Show DClause 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Show DCon 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

showsPrec :: Int -> DCon -> ShowS #

show :: DCon -> String #

showList :: [DCon] -> ShowS #

Show DConFields 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Show DDec 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

showsPrec :: Int -> DDec -> ShowS #

show :: DDec -> String #

showList :: [DDec] -> ShowS #

Show DDerivClause 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Show DDerivStrategy 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Show DExp 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

showsPrec :: Int -> DExp -> ShowS #

show :: DExp -> String #

showList :: [DExp] -> ShowS #

Show DFamilyResultSig 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Show DForallTelescope 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Show DForeign 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Show DInfo 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

showsPrec :: Int -> DInfo -> ShowS #

show :: DInfo -> String #

showList :: [DInfo] -> ShowS #

Show DLetDec 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Show DMatch 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Show DPat 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

showsPrec :: Int -> DPat -> ShowS #

show :: DPat -> String #

showList :: [DPat] -> ShowS #

Show DPatSynDir 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Show DPragma 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Show DRuleBndr 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Show DTySynEqn 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Show DType 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

showsPrec :: Int -> DType -> ShowS #

show :: DType -> String #

showList :: [DType] -> ShowS #

Show DTypeFamilyHead 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Show NewOrData 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Show DFunArgs 
Instance details

Defined in Language.Haskell.TH.Desugar.Core

Show DTypeArg 
Instance details

Defined in Language.Haskell.TH.Desugar.Core

Show DVisFunArg 
Instance details

Defined in Language.Haskell.TH.Desugar.Core

Show DayOfWeek 
Instance details

Defined in Data.Time.Calendar.Week

Show DiffTime 
Instance details

Defined in Data.Time.Clock.Internal.DiffTime

Show NominalDiffTime 
Instance details

Defined in Data.Time.Clock.Internal.NominalDiffTime

Show LocalTime 
Instance details

Defined in Data.Time.LocalTime.Internal.LocalTime

Show TimeOfDay 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeOfDay

Show TimeZone

This only shows the time zone name, or offset if the name is empty.

Instance details

Defined in Data.Time.LocalTime.Internal.TimeZone

Show ZonedTime 
Instance details

Defined in Data.Time.LocalTime.Internal.ZonedTime

Show Undefined 
Instance details

Defined in Universum.Debug

Show Bug 
Instance details

Defined in Universum.Exception

Methods

showsPrec :: Int -> Bug -> ShowS #

show :: Bug -> String #

showList :: [Bug] -> ShowS #

Show UUID

Pretty prints a UUID (without quotation marks). See also toString.

>>> show nil
"00000000-0000-0000-0000-000000000000"
Instance details

Defined in Data.UUID.Types.Internal

Methods

showsPrec :: Int -> UUID -> ShowS #

show :: UUID -> String #

showList :: [UUID] -> ShowS #

Show UnpackedUUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

showsPrec :: Int -> UnpackedUUID -> ShowS #

show :: UnpackedUUID -> String #

showList :: [UnpackedUUID] -> ShowS #

Show Doc 
Instance details

Defined in Text.PrettyPrint.Leijen.Text

Methods

showsPrec :: Int -> Doc -> ShowS #

show :: Doc -> String #

showList :: [Doc] -> ShowS #

Show SimpleDoc 
Instance details

Defined in Text.PrettyPrint.Leijen.Text

Show Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

showsPrec :: Int -> Word8 -> ShowS #

show :: Word8 -> String #

showList :: [Word8] -> ShowS #

Show Integer

Since: base-2.1

Instance details

Defined in GHC.Show

Show Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Show

Show ()

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> () -> ShowS #

show :: () -> String #

showList :: [()] -> ShowS #

Show Bool

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> Bool -> ShowS #

show :: Bool -> String #

showList :: [Bool] -> ShowS #

Show Char

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> Char -> ShowS #

show :: Char -> String #

showList :: [Char] -> ShowS #

Show Int

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> Int -> ShowS #

show :: Int -> String #

showList :: [Int] -> ShowS #

Show RuntimeRep

Since: base-4.11.0.0

Instance details

Defined in GHC.Show

Show VecCount

Since: base-4.11.0.0

Instance details

Defined in GHC.Show

Show VecElem

Since: base-4.11.0.0

Instance details

Defined in GHC.Show

Show Word

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> Word -> ShowS #

show :: Word -> String #

showList :: [Word] -> ShowS #

() :=> (Show (a :- b)) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Show (a :- b) #

() :=> (Show (Dict a)) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Show (Dict a) #

() :=> (Show Ordering) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Show Ordering #

() :=> (Show Natural) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Show Natural #

() :=> (Show ()) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Show () #

() :=> (Show Bool) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Show Bool #

() :=> (Show Char) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Show Char #

() :=> (Show Int) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Show Int #

() :=> (Show Word) 
Instance details

Defined in Data.Constraint

Methods

ins :: () :- Show Word #

Class () (Show a) 
Instance details

Defined in Data.Constraint

Methods

cls :: Show a :- () #

Show a => Show (First' a) 
Instance details

Defined in Distribution.Compat.Semigroup

Methods

showsPrec :: Int -> First' a -> ShowS #

show :: First' a -> String #

showList :: [First' a] -> ShowS #

Show a => Show (Last' a) 
Instance details

Defined in Distribution.Compat.Semigroup

Methods

showsPrec :: Int -> Last' a -> ShowS #

show :: Last' a -> String #

showList :: [Last' a] -> ShowS #

Show a => Show (Option' a) 
Instance details

Defined in Distribution.Compat.Semigroup

Methods

showsPrec :: Int -> Option' a -> ShowS #

show :: Option' a -> String #

showList :: [Option' a] -> ShowS #

Show v => Show (KeyMap v) 
Instance details

Defined in Data.Aeson.KeyMap

Methods

showsPrec :: Int -> KeyMap v -> ShowS #

show :: KeyMap v -> String #

showList :: [KeyMap v] -> ShowS #

Show a => Show (IResult a) 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

showsPrec :: Int -> IResult a -> ShowS #

show :: IResult a -> String #

showList :: [IResult a] -> ShowS #

Show a => Show (Result a) 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

showsPrec :: Int -> Result a -> ShowS #

show :: Result a -> String #

showList :: [Result a] -> ShowS #

Show a => Show (ZipList a)

Since: base-4.7.0.0

Instance details

Defined in Control.Applicative

Methods

showsPrec :: Int -> ZipList a -> ShowS #

show :: ZipList a -> String #

showList :: [ZipList a] -> ShowS #

Show a => Show (Complex a)

Since: base-2.1

Instance details

Defined in Data.Complex

Methods

showsPrec :: Int -> Complex a -> ShowS #

show :: Complex a -> String #

showList :: [Complex a] -> ShowS #

Show a => Show (Identity a)

This instance would be equivalent to the derived instances of the Identity newtype if the runIdentity field were removed

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Methods

showsPrec :: Int -> Identity a -> ShowS #

show :: Identity a -> String #

showList :: [Identity a] -> ShowS #

Show a => Show (First a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

showsPrec :: Int -> First a -> ShowS #

show :: First a -> String #

showList :: [First a] -> ShowS #

Show a => Show (Last a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

showsPrec :: Int -> Last a -> ShowS #

show :: Last a -> String #

showList :: [Last a] -> ShowS #

Show a => Show (Down a)

This instance would be equivalent to the derived instances of the Down newtype if the getDown field were removed

Since: base-4.7.0.0

Instance details

Defined in Data.Ord

Methods

showsPrec :: Int -> Down a -> ShowS #

show :: Down a -> String #

showList :: [Down a] -> ShowS #

Show a => Show (First a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

showsPrec :: Int -> First a -> ShowS #

show :: First a -> String #

showList :: [First a] -> ShowS #

Show a => Show (Last a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

showsPrec :: Int -> Last a -> ShowS #

show :: Last a -> String #

showList :: [Last a] -> ShowS #

Show a => Show (Max a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

showsPrec :: Int -> Max a -> ShowS #

show :: Max a -> String #

showList :: [Max a] -> ShowS #

Show a => Show (Min a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

showsPrec :: Int -> Min a -> ShowS #

show :: Min a -> String #

showList :: [Min a] -> ShowS #

Show a => Show (Option a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

showsPrec :: Int -> Option a -> ShowS #

show :: Option a -> String #

showList :: [Option a] -> ShowS #

Show m => Show (WrappedMonoid m)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Show a => Show (Dual a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

showsPrec :: Int -> Dual a -> ShowS #

show :: Dual a -> String #

showList :: [Dual a] -> ShowS #

Show a => Show (Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

showsPrec :: Int -> Product a -> ShowS #

show :: Product a -> String #

showList :: [Product a] -> ShowS #

Show a => Show (Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

showsPrec :: Int -> Sum a -> ShowS #

show :: Sum a -> String #

showList :: [Sum a] -> ShowS #

Show a => Show (NonEmpty a)

Since: base-4.11.0.0

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> NonEmpty a -> ShowS #

show :: NonEmpty a -> String #

showList :: [NonEmpty a] -> ShowS #

Show (ForeignPtr a)

Since: base-2.1

Instance details

Defined in GHC.ForeignPtr

Show p => Show (Par1 p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> Par1 p -> ShowS #

show :: Par1 p -> String #

showList :: [Par1 p] -> ShowS #

Show (FunPtr a)

Since: base-2.1

Instance details

Defined in GHC.Ptr

Methods

showsPrec :: Int -> FunPtr a -> ShowS #

show :: FunPtr a -> String #

showList :: [FunPtr a] -> ShowS #

Show (Ptr a)

Since: base-2.1

Instance details

Defined in GHC.Ptr

Methods

showsPrec :: Int -> Ptr a -> ShowS #

show :: Ptr a -> String #

showList :: [Ptr a] -> ShowS #

Show a => Show (Ratio a)

Since: base-2.0.1

Instance details

Defined in GHC.Real

Methods

showsPrec :: Int -> Ratio a -> ShowS #

show :: Ratio a -> String #

showList :: [Ratio a] -> ShowS #

Show (Bits n) 
Instance details

Defined in Basement.Bits

Methods

showsPrec :: Int -> Bits n -> ShowS #

show :: Bits n -> String #

showList :: [Bits n] -> ShowS #

(PrimType ty, Show ty) => Show (Block ty) 
Instance details

Defined in Basement.Block.Base

Methods

showsPrec :: Int -> Block ty -> ShowS #

show :: Block ty -> String #

showList :: [Block ty] -> ShowS #

Show (Zn n) 
Instance details

Defined in Basement.Bounded

Methods

showsPrec :: Int -> Zn n -> ShowS #

show :: Zn n -> String #

showList :: [Zn n] -> ShowS #

Show (Zn64 n) 
Instance details

Defined in Basement.Bounded

Methods

showsPrec :: Int -> Zn64 n -> ShowS #

show :: Zn64 n -> String #

showList :: [Zn64 n] -> ShowS #

Show a => Show (Array a) 
Instance details

Defined in Basement.BoxedArray

Methods

showsPrec :: Int -> Array a -> ShowS #

show :: Array a -> String #

showList :: [Array a] -> ShowS #

Show a => Show (NonEmpty a) 
Instance details

Defined in Basement.NonEmpty

Methods

showsPrec :: Int -> NonEmpty a -> ShowS #

show :: NonEmpty a -> String #

showList :: [NonEmpty a] -> ShowS #

Show (CountOf ty) 
Instance details

Defined in Basement.Types.OffsetSize

Methods

showsPrec :: Int -> CountOf ty -> ShowS #

show :: CountOf ty -> String #

showList :: [CountOf ty] -> ShowS #

Show (Offset ty) 
Instance details

Defined in Basement.Types.OffsetSize

Methods

showsPrec :: Int -> Offset ty -> ShowS #

show :: Offset ty -> String #

showList :: [Offset ty] -> ShowS #

(PrimType ty, Show ty) => Show (UArray ty) 
Instance details

Defined in Basement.UArray.Base

Methods

showsPrec :: Int -> UArray ty -> ShowS #

show :: UArray ty -> String #

showList :: [UArray ty] -> ShowS #

Show (Dict a) 
Instance details

Defined in Data.Constraint

Methods

showsPrec :: Int -> Dict a -> ShowS #

show :: Dict a -> String #

showList :: [Dict a] -> ShowS #

Show vertex => Show (SCC vertex)

Since: containers-0.5.9

Instance details

Defined in Data.Graph

Methods

showsPrec :: Int -> SCC vertex -> ShowS #

show :: SCC vertex -> String #

showList :: [SCC vertex] -> ShowS #

Show a => Show (IntMap a) 
Instance details

Defined in Data.IntMap.Internal

Methods

showsPrec :: Int -> IntMap a -> ShowS #

show :: IntMap a -> String #

showList :: [IntMap a] -> ShowS #

Show a => Show (Seq a) 
Instance details

Defined in Data.Sequence.Internal

Methods

showsPrec :: Int -> Seq a -> ShowS #

show :: Seq a -> String #

showList :: [Seq a] -> ShowS #

Show a => Show (ViewL a) 
Instance details

Defined in Data.Sequence.Internal

Methods

showsPrec :: Int -> ViewL a -> ShowS #

show :: ViewL a -> String #

showList :: [ViewL a] -> ShowS #

Show a => Show (ViewR a) 
Instance details

Defined in Data.Sequence.Internal

Methods

showsPrec :: Int -> ViewR a -> ShowS #

show :: ViewR a -> String #

showList :: [ViewR a] -> ShowS #

Show a => Show (Set a) 
Instance details

Defined in Data.Set.Internal

Methods

showsPrec :: Int -> Set a -> ShowS #

show :: Set a -> String #

showList :: [Set a] -> ShowS #

Show a => Show (Tree a) 
Instance details

Defined in Data.Tree

Methods

showsPrec :: Int -> Tree a -> ShowS #

show :: Tree a -> String #

showList :: [Tree a] -> ShowS #

Show a => Show (CryptoFailable a) 
Instance details

Defined in Crypto.Error.Types

Show (Blake2b bitlen) 
Instance details

Defined in Crypto.Hash.Blake2

Methods

showsPrec :: Int -> Blake2b bitlen -> ShowS #

show :: Blake2b bitlen -> String #

showList :: [Blake2b bitlen] -> ShowS #

Show (Blake2bp bitlen) 
Instance details

Defined in Crypto.Hash.Blake2

Methods

showsPrec :: Int -> Blake2bp bitlen -> ShowS #

show :: Blake2bp bitlen -> String #

showList :: [Blake2bp bitlen] -> ShowS #

Show (Blake2s bitlen) 
Instance details

Defined in Crypto.Hash.Blake2

Methods

showsPrec :: Int -> Blake2s bitlen -> ShowS #

show :: Blake2s bitlen -> String #

showList :: [Blake2s bitlen] -> ShowS #

Show (Blake2sp bitlen) 
Instance details

Defined in Crypto.Hash.Blake2

Methods

showsPrec :: Int -> Blake2sp bitlen -> ShowS #

show :: Blake2sp bitlen -> String #

showList :: [Blake2sp bitlen] -> ShowS #

Show (SHAKE128 bitlen) 
Instance details

Defined in Crypto.Hash.SHAKE

Methods

showsPrec :: Int -> SHAKE128 bitlen -> ShowS #

show :: SHAKE128 bitlen -> String #

showList :: [SHAKE128 bitlen] -> ShowS #

Show (SHAKE256 bitlen) 
Instance details

Defined in Crypto.Hash.SHAKE

Methods

showsPrec :: Int -> SHAKE256 bitlen -> ShowS #

show :: SHAKE256 bitlen -> String #

showList :: [SHAKE256 bitlen] -> ShowS #

Show (Digest a) 
Instance details

Defined in Crypto.Hash.Types

Methods

showsPrec :: Int -> Digest a -> ShowS #

show :: Digest a -> String #

showList :: [Digest a] -> ShowS #

Show1 f => Show (Fix f) 
Instance details

Defined in Data.Fix

Methods

showsPrec :: Int -> Fix f -> ShowS #

show :: Fix f -> String #

showList :: [Fix f] -> ShowS #

(Functor f, Show1 f) => Show (Mu f) 
Instance details

Defined in Data.Fix

Methods

showsPrec :: Int -> Mu f -> ShowS #

show :: Mu f -> String #

showList :: [Mu f] -> ShowS #

(Functor f, Show1 f) => Show (Nu f) 
Instance details

Defined in Data.Fix

Methods

showsPrec :: Int -> Nu f -> ShowS #

show :: Nu f -> String #

showList :: [Nu f] -> ShowS #

Show a => Show (DNonEmpty a) 
Instance details

Defined in Data.DList.DNonEmpty.Internal

Show a => Show (DList a) 
Instance details

Defined in Data.DList.Internal

Methods

showsPrec :: Int -> DList a -> ShowS #

show :: DList a -> String #

showList :: [DList a] -> ShowS #

Show a => Show (ExitCase a) 
Instance details

Defined in Control.Monad.Catch

Methods

showsPrec :: Int -> ExitCase a -> ShowS #

show :: ExitCase a -> String #

showList :: [ExitCase a] -> ShowS #

Show a => Show (Hex a) 
Instance details

Defined in Data.Text.Format.Types

Methods

showsPrec :: Int -> Hex a -> ShowS #

show :: Hex a -> String #

showList :: [Hex a] -> ShowS #

Show a => Show (Shown a) 
Instance details

Defined in Data.Text.Format.Types

Methods

showsPrec :: Int -> Shown a -> ShowS #

show :: Shown a -> String #

showList :: [Shown a] -> ShowS #

Show (Binary p) 
Instance details

Defined in Data.Field.Galois.Binary

Methods

showsPrec :: Int -> Binary p -> ShowS #

show :: Binary p -> String #

showList :: [Binary p] -> ShowS #

KnownNat p => Show (Prime p) 
Instance details

Defined in Data.Field.Galois.Prime

Methods

showsPrec :: Int -> Prime p -> ShowS #

show :: Prime p -> String #

showList :: [Prime p] -> ShowS #

Show a => Show (Hashed a) 
Instance details

Defined in Data.Hashable.Class

Methods

showsPrec :: Int -> Hashed a -> ShowS #

show :: Hashed a -> String #

showList :: [Hashed a] -> ShowS #

Show a => Show (OpenChestT a) Source # 
Instance details

Defined in Lorentz.Bytes

Show (Packed a) Source # 
Instance details

Defined in Lorentz.Bytes

Methods

showsPrec :: Int -> Packed a -> ShowS #

show :: Packed a -> String #

showList :: [Packed a] -> ShowS #

Show (TSignature a) Source # 
Instance details

Defined in Lorentz.Bytes

Show (EpCallingDesc info) Source # 
Instance details

Defined in Lorentz.Entrypoints.Core

Methods

showsPrec :: Int -> EpCallingDesc info -> ShowS #

show :: EpCallingDesc info -> String #

showList :: [EpCallingDesc info] -> ShowS #

Show (CustomErrorRep tag) => Show (CustomError tag) Source # 
Instance details

Defined in Lorentz.Errors

Methods

showsPrec :: Int -> CustomError tag -> ShowS #

show :: CustomError tag -> String #

showList :: [CustomError tag] -> ShowS #

Show (ConstrainedSome Show) Source # 
Instance details

Defined in Lorentz.UParam

Show (UParam entries) Source # 
Instance details

Defined in Lorentz.UParam

Methods

showsPrec :: Int -> UParam entries -> ShowS #

show :: UParam entries -> String #

showList :: [UParam entries] -> ShowS #

Show a => Show (ReadTicket a) Source # 
Instance details

Defined in Lorentz.Value

Show e => Show (ErrorFancy e) 
Instance details

Defined in Text.Megaparsec.Error

Show t => Show (ErrorItem t) 
Instance details

Defined in Text.Megaparsec.Error

Show s => Show (PosState s) 
Instance details

Defined in Text.Megaparsec.State

Methods

showsPrec :: Int -> PosState s -> ShowS #

show :: PosState s -> String #

showList :: [PosState s] -> ShowS #

KnownNat m => Show (Mod m) 
Instance details

Defined in Data.Mod

Methods

showsPrec :: Int -> Mod m -> ShowS #

show :: Mod m -> String #

showList :: [Mod m] -> ShowS #

Show (Exp x) => Show (FromExpError x) 
Instance details

Defined in Morley.Micheline.Class

Methods

showsPrec :: Int -> FromExpError x -> ShowS #

show :: FromExpError x -> String #

showList :: [FromExpError x] -> ShowS #

ExpAllExtrasConstrainted Show x => Show (Exp x) 
Instance details

Defined in Morley.Micheline.Expression

Methods

showsPrec :: Int -> Exp x -> ShowS #

show :: Exp x -> String #

showList :: [Exp x] -> ShowS #

Show (Exp x) => Show (MichelinePrimAp x) 
Instance details

Defined in Morley.Micheline.Expression

Methods

showsPrec :: Int -> MichelinePrimAp x -> ShowS #

show :: MichelinePrimAp x -> String #

showList :: [MichelinePrimAp x] -> ShowS #

Show a => Show (StringEncode a) 
Instance details

Defined in Morley.Micheline.Json

Methods

showsPrec :: Int -> StringEncode a -> ShowS #

show :: StringEncode a -> String #

showList :: [StringEncode a] -> ShowS #

Show ext => Show (InterpretError ext) 
Instance details

Defined in Morley.Michelson.Interpret

Methods

showsPrec :: Int -> InterpretError ext -> ShowS #

show :: InterpretError ext -> String #

showList :: [InterpretError ext] -> ShowS #

Show ext => Show (MichelsonFailed ext) 
Instance details

Defined in Morley.Michelson.Interpret

Methods

showsPrec :: Int -> MichelsonFailed ext -> ShowS #

show :: MichelsonFailed ext -> String #

showList :: [MichelsonFailed ext] -> ShowS #

Show ext => Show (MichelsonFailureWithStack ext) 
Instance details

Defined in Morley.Michelson.Interpret

Methods

showsPrec :: Int -> MichelsonFailureWithStack ext -> ShowS #

show :: MichelsonFailureWithStack ext -> String #

showList :: [MichelsonFailureWithStack ext] -> ShowS #

Show (StkEl t) 
Instance details

Defined in Morley.Michelson.Interpret

Methods

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

show :: StkEl t -> String #

showList :: [StkEl t] -> ShowS #

Show op => Show (TcError' op) 
Instance details

Defined in Morley.Michelson.TypeCheck.Error

Methods

showsPrec :: Int -> TcError' op -> ShowS #

show :: TcError' op -> String #

showList :: [TcError' op] -> ShowS #

Show op => Show (IllTypedInstr op) 
Instance details

Defined in Morley.Michelson.TypeCheck.TypeCheckedOp

Methods

showsPrec :: Int -> IllTypedInstr op -> ShowS #

show :: IllTypedInstr op -> String #

showList :: [IllTypedInstr op] -> ShowS #

Show op => Show (TypeCheckedOp op) 
Instance details

Defined in Morley.Michelson.TypeCheck.TypeCheckedOp

Methods

showsPrec :: Int -> TypeCheckedOp op -> ShowS #

show :: TypeCheckedOp op -> String #

showList :: [TypeCheckedOp op] -> ShowS #

Show (HST ts) 
Instance details

Defined in Morley.Michelson.TypeCheck.Types

Methods

showsPrec :: Int -> HST ts -> ShowS #

show :: HST ts -> String #

showList :: [HST ts] -> ShowS #

Show (SomeTcInstr inp) 
Instance details

Defined in Morley.Michelson.TypeCheck.Types

Methods

showsPrec :: Int -> SomeTcInstr inp -> ShowS #

show :: SomeTcInstr inp -> String #

showList :: [SomeTcInstr inp] -> ShowS #

Show (SomeTcInstrOut inp) 
Instance details

Defined in Morley.Michelson.TypeCheck.Types

Methods

showsPrec :: Int -> SomeTcInstrOut inp -> ShowS #

show :: SomeTcInstrOut inp -> String #

showList :: [SomeTcInstrOut inp] -> ShowS #

Show (AnnotatedValue v) 
Instance details

Defined in Morley.Michelson.Typed.AnnotatedValue

Methods

showsPrec :: Int -> AnnotatedValue v -> ShowS #

show :: AnnotatedValue v -> String #

showList :: [AnnotatedValue v] -> ShowS #

Each '[Show] rs => Show (Anns rs) 
Instance details

Defined in Morley.Michelson.Typed.Annotation

Methods

showsPrec :: Int -> Anns rs -> ShowS #

show :: Anns rs -> String #

showList :: [Anns rs] -> ShowS #

Show (Notes t) 
Instance details

Defined in Morley.Michelson.Typed.Annotation

Methods

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

show :: Notes t -> String #

showList :: [Notes t] -> ShowS #

Show (ParamNotes t) 
Instance details

Defined in Morley.Michelson.Typed.Entrypoints

Methods

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

show :: ParamNotes t -> String #

showList :: [ParamNotes t] -> ShowS #

Show (SomeEntrypointCallT arg) 
Instance details

Defined in Morley.Michelson.Typed.Entrypoints

Methods

showsPrec :: Int -> SomeEntrypointCallT arg -> ShowS #

show :: SomeEntrypointCallT arg -> String #

showList :: [SomeEntrypointCallT arg] -> ShowS #

Show (ContractRef arg) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Methods

showsPrec :: Int -> ContractRef arg -> ShowS #

show :: ContractRef arg -> String #

showList :: [ContractRef arg] -> ShowS #

Show arg => Show (Ticket arg) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Methods

showsPrec :: Int -> Ticket arg -> ShowS #

show :: Ticket arg -> String #

showList :: [Ticket arg] -> ShowS #

Show (ExtInstr s) 
Instance details

Defined in Morley.Michelson.Typed.Instr

Methods

showsPrec :: Int -> ExtInstr s -> ShowS #

show :: ExtInstr s -> String #

showList :: [ExtInstr s] -> ShowS #

Show (PrintComment st) 
Instance details

Defined in Morley.Michelson.Typed.Instr

Methods

showsPrec :: Int -> PrintComment st -> ShowS #

show :: PrintComment st -> String #

showList :: [PrintComment st] -> ShowS #

Show (StackRef st) 
Instance details

Defined in Morley.Michelson.Typed.Instr

Methods

showsPrec :: Int -> StackRef st -> ShowS #

show :: StackRef st -> String #

showList :: [StackRef st] -> ShowS #

Show (TestAssert s) 
Instance details

Defined in Morley.Michelson.Typed.Instr

Methods

showsPrec :: Int -> TestAssert s -> ShowS #

show :: TestAssert s -> String #

showList :: [TestAssert s] -> ShowS #

Show (SingT x) 
Instance details

Defined in Morley.Michelson.Typed.Sing

Methods

showsPrec :: Int -> SingT x -> ShowS #

show :: SingT x -> String #

showList :: [SingT x] -> ShowS #

Show (Operation' instr) 
Instance details

Defined in Morley.Michelson.Typed.Value

Methods

showsPrec :: Int -> Operation' instr -> ShowS #

show :: Operation' instr -> String #

showList :: [Operation' instr] -> ShowS #

(forall (i :: [T]) (o :: [T]). Show (instr i o)) => Show (SomeViewsSet' instr) 
Instance details

Defined in Morley.Michelson.Typed.View

Methods

showsPrec :: Int -> SomeViewsSet' instr -> ShowS #

show :: SomeViewsSet' instr -> String #

showList :: [SomeViewsSet' instr] -> ShowS #

Show op => Show (Contract' op) 
Instance details

Defined in Morley.Michelson.Untyped.Contract

Methods

showsPrec :: Int -> Contract' op -> ShowS #

show :: Contract' op -> String #

showList :: [Contract' op] -> ShowS #

Show op => Show (ContractBlock op) 
Instance details

Defined in Morley.Michelson.Untyped.Contract

Methods

showsPrec :: Int -> ContractBlock op -> ShowS #

show :: ContractBlock op -> String #

showList :: [ContractBlock op] -> ShowS #

Show op => Show (ExtInstrAbstract op) 
Instance details

Defined in Morley.Michelson.Untyped.Ext

Methods

showsPrec :: Int -> ExtInstrAbstract op -> ShowS #

show :: ExtInstrAbstract op -> String #

showList :: [ExtInstrAbstract op] -> ShowS #

Show op => Show (TestAssert op) 
Instance details

Defined in Morley.Michelson.Untyped.Ext

Methods

showsPrec :: Int -> TestAssert op -> ShowS #

show :: TestAssert op -> String #

showList :: [TestAssert op] -> ShowS #

Show op => Show (InstrAbstract op) 
Instance details

Defined in Morley.Michelson.Untyped.Instr

Methods

showsPrec :: Int -> InstrAbstract op -> ShowS #

show :: InstrAbstract op -> String #

showList :: [InstrAbstract op] -> ShowS #

Show op => Show (Elt op) 
Instance details

Defined in Morley.Michelson.Untyped.Value

Methods

showsPrec :: Int -> Elt op -> ShowS #

show :: Elt op -> String #

showList :: [Elt op] -> ShowS #

Show op => Show (Value' op) 
Instance details

Defined in Morley.Michelson.Untyped.Value

Methods

showsPrec :: Int -> Value' op -> ShowS #

show :: Value' op -> String #

showList :: [Value' op] -> ShowS #

Show op => Show (View' op) 
Instance details

Defined in Morley.Michelson.Untyped.View

Methods

showsPrec :: Int -> View' op -> ShowS #

show :: View' op -> String #

showList :: [View' op] -> ShowS #

Show (KindedAddress kind) 
Instance details

Defined in Morley.Tezos.Address

Methods

showsPrec :: Int -> KindedAddress kind -> ShowS #

show :: KindedAddress kind -> String #

showList :: [KindedAddress kind] -> ShowS #

Show (AddressOrAlias kind) 
Instance details

Defined in Morley.Tezos.Address.Alias

Methods

showsPrec :: Int -> AddressOrAlias kind -> ShowS #

show :: AddressOrAlias kind -> String #

showList :: [AddressOrAlias kind] -> ShowS #

Show (Alias kind) 
Instance details

Defined in Morley.Tezos.Address.Alias

Methods

showsPrec :: Int -> Alias kind -> ShowS #

show :: Alias kind -> String #

showList :: [Alias kind] -> ShowS #

Show (Hash kind) 
Instance details

Defined in Morley.Tezos.Crypto

Methods

showsPrec :: Int -> Hash kind -> ShowS #

show :: Hash kind -> String #

showList :: [Hash kind] -> ShowS #

Show (HashTag kind) 
Instance details

Defined in Morley.Tezos.Crypto

Methods

showsPrec :: Int -> HashTag kind -> ShowS #

show :: HashTag kind -> String #

showList :: [HashTag kind] -> ShowS #

Show (Label name) 
Instance details

Defined in Morley.Util.Label

Methods

showsPrec :: Int -> Label name -> ShowS #

show :: Label name -> String #

showList :: [Label name] -> ShowS #

Show a => Show (MismatchError a) 
Instance details

Defined in Morley.Util.MismatchError

Methods

showsPrec :: Int -> MismatchError a -> ShowS #

show :: MismatchError a -> String #

showList :: [MismatchError a] -> ShowS #

Show (SingNat n) 
Instance details

Defined in Morley.Util.Peano

Methods

showsPrec :: Int -> SingNat n -> ShowS #

show :: SingNat n -> String #

showList :: [SingNat n] -> ShowS #

Show (PeanoNatural n) 
Instance details

Defined in Morley.Util.PeanoNatural

Methods

showsPrec :: Int -> PeanoNatural n -> ShowS #

show :: PeanoNatural n -> String #

showList :: [PeanoNatural n] -> ShowS #

Show a => Show (SomeSizedList a) 
Instance details

Defined in Morley.Util.SizedList

Methods

showsPrec :: Int -> SomeSizedList a -> ShowS #

show :: SomeSizedList a -> String #

showList :: [SomeSizedList a] -> ShowS #

Show a => Show (OptTree a) 
Instance details

Defined in Options.Applicative.Types

Methods

showsPrec :: Int -> OptTree a -> ShowS #

show :: OptTree a -> String #

showList :: [OptTree a] -> ShowS #

Show (Option a) 
Instance details

Defined in Options.Applicative.Types

Methods

showsPrec :: Int -> Option a -> ShowS #

show :: Option a -> String #

showList :: [Option a] -> ShowS #

Show h => Show (ParserFailure h) 
Instance details

Defined in Options.Applicative.Types

Show a => Show (ParserResult a) 
Instance details

Defined in Options.Applicative.Types

Show a => Show (AnnotDetails a) 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Show (Doc a) 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

showsPrec :: Int -> Doc a -> ShowS #

show :: Doc a -> String #

showList :: [Doc a] -> ShowS #

Show a => Show (Span a) 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

showsPrec :: Int -> Span a -> ShowS #

show :: Span a -> String #

showList :: [Span a] -> ShowS #

Show a => Show (Array a) 
Instance details

Defined in Data.Primitive.Array

Methods

showsPrec :: Int -> Array a -> ShowS #

show :: Array a -> String #

showList :: [Array a] -> ShowS #

(Show a, Prim a) => Show (PrimArray a)

Since: primitive-0.6.4.0

Instance details

Defined in Data.Primitive.PrimArray

Show a => Show (SmallArray a) 
Instance details

Defined in Data.Primitive.SmallArray

Show g => Show (StateGen g) 
Instance details

Defined in System.Random.Internal

Methods

showsPrec :: Int -> StateGen g -> ShowS #

show :: StateGen g -> String #

showList :: [StateGen g] -> ShowS #

Show g => Show (AtomicGen g) 
Instance details

Defined in System.Random.Stateful

Show g => Show (IOGen g) 
Instance details

Defined in System.Random.Stateful

Methods

showsPrec :: Int -> IOGen g -> ShowS #

show :: IOGen g -> String #

showList :: [IOGen g] -> ShowS #

Show g => Show (STGen g) 
Instance details

Defined in System.Random.Stateful

Methods

showsPrec :: Int -> STGen g -> ShowS #

show :: STGen g -> String #

showList :: [STGen g] -> ShowS #

Show g => Show (TGen g) 
Instance details

Defined in System.Random.Stateful

Methods

showsPrec :: Int -> TGen g -> ShowS #

show :: TGen g -> String #

showList :: [TGen g] -> ShowS #

Show a => Show (Add a) 
Instance details

Defined in Data.Semiring

Methods

showsPrec :: Int -> Add a -> ShowS #

show :: Add a -> String #

showList :: [Add a] -> ShowS #

Show (IntSetOf a) 
Instance details

Defined in Data.Semiring

Methods

showsPrec :: Int -> IntSetOf a -> ShowS #

show :: IntSetOf a -> String #

showList :: [IntSetOf a] -> ShowS #

Show a => Show (Mul a) 
Instance details

Defined in Data.Semiring

Methods

showsPrec :: Int -> Mul a -> ShowS #

show :: Mul a -> String #

showList :: [Mul a] -> ShowS #

Show a => Show (WrappedNum a) 
Instance details

Defined in Data.Semiring

Show (SBool z) 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

showsPrec :: Int -> SBool z -> ShowS #

show :: SBool z -> String #

showList :: [SBool z] -> ShowS #

Show (SOrdering z) 
Instance details

Defined in Data.Singletons.Base.Instances

Show (STuple0 z) 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

showsPrec :: Int -> STuple0 z -> ShowS #

show :: STuple0 z -> String #

showList :: [STuple0 z] -> ShowS #

Show (SVoid z) 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

showsPrec :: Int -> SVoid z -> ShowS #

show :: SVoid z -> String #

showList :: [SVoid z] -> ShowS #

Show (SNat n) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Methods

showsPrec :: Int -> SNat n -> ShowS #

show :: SNat n -> String #

showList :: [SNat n] -> ShowS #

Show (SSymbol s) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Methods

showsPrec :: Int -> SSymbol s -> ShowS #

show :: SSymbol s -> String #

showList :: [SSymbol s] -> ShowS #

Show a => Show (Maybe a) 
Instance details

Defined in Data.Strict.Maybe

Methods

showsPrec :: Int -> Maybe a -> ShowS #

show :: Maybe a -> String #

showList :: [Maybe a] -> ShowS #

Show flag => Show (TyVarBndr flag) 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> TyVarBndr flag -> ShowS #

show :: TyVarBndr flag -> String #

showList :: [TyVarBndr flag] -> ShowS #

Show flag => Show (DTyVarBndr flag) 
Instance details

Defined in Language.Haskell.TH.Desugar.AST

Methods

showsPrec :: Int -> DTyVarBndr flag -> ShowS #

show :: DTyVarBndr flag -> String #

showList :: [DTyVarBndr flag] -> ShowS #

Show a => Show (HashSet a) 
Instance details

Defined in Data.HashSet.Internal

Methods

showsPrec :: Int -> HashSet a -> ShowS #

show :: HashSet a -> String #

showList :: [HashSet a] -> ShowS #

Show a => Show (Vector a) 
Instance details

Defined in Data.Vector

Methods

showsPrec :: Int -> Vector a -> ShowS #

show :: Vector a -> String #

showList :: [Vector a] -> ShowS #

(Show a, Prim a) => Show (Vector a) 
Instance details

Defined in Data.Vector.Primitive

Methods

showsPrec :: Int -> Vector a -> ShowS #

show :: Vector a -> String #

showList :: [Vector a] -> ShowS #

(Show a, Storable a) => Show (Vector a) 
Instance details

Defined in Data.Vector.Storable

Methods

showsPrec :: Int -> Vector a -> ShowS #

show :: Vector a -> String #

showList :: [Vector a] -> ShowS #

(Show t, KnownSymbol s) => Show (ElField '(s, t)) 
Instance details

Defined in Data.Vinyl.Functor

Methods

showsPrec :: Int -> ElField '(s, t) -> ShowS #

show :: ElField '(s, t) -> String #

showList :: [ElField '(s, t)] -> ShowS #

Show a => Show (Identity a) 
Instance details

Defined in Data.Vinyl.Functor

Methods

showsPrec :: Int -> Identity a -> ShowS #

show :: Identity a -> String #

showList :: [Identity a] -> ShowS #

Show a => Show (Thunk a) 
Instance details

Defined in Data.Vinyl.Functor

Methods

showsPrec :: Int -> Thunk a -> ShowS #

show :: Thunk a -> String #

showList :: [Thunk a] -> ShowS #

Show a => Show (Maybe a)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> Maybe a -> ShowS #

show :: Maybe a -> String #

showList :: [Maybe a] -> ShowS #

Show a => Show (a)

Since: base-4.15

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a) -> ShowS #

show :: (a) -> String #

showList :: [(a)] -> ShowS #

Show a => Show [a]

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> [a] -> ShowS #

show :: [a] -> String #

showList :: [[a]] -> ShowS #

(Show a) :=> (Show (Complex a)) 
Instance details

Defined in Data.Constraint

Methods

ins :: Show a :- Show (Complex a) #

(Show a) :=> (Show (Const a b)) 
Instance details

Defined in Data.Constraint

Methods

ins :: Show a :- Show (Const a b) #

(Show a) :=> (Show (Identity a)) 
Instance details

Defined in Data.Constraint

Methods

ins :: Show a :- Show (Identity a) #

(Show a) :=> (Show (Maybe a)) 
Instance details

Defined in Data.Constraint

Methods

ins :: Show a :- Show (Maybe a) #

(Show a) :=> (Show [a]) 
Instance details

Defined in Data.Constraint

Methods

ins :: Show a :- Show [a] #

Show a => Show (OddWord a n) 
Instance details

Defined in Data.Word.Odd

Methods

showsPrec :: Int -> OddWord a n -> ShowS #

show :: OddWord a n -> String #

showList :: [OddWord a n] -> ShowS #

(Show i, Show r) => Show (IResult i r) 
Instance details

Defined in Data.Attoparsec.Internal.Types

Methods

showsPrec :: Int -> IResult i r -> ShowS #

show :: IResult i r -> String #

showList :: [IResult i r] -> ShowS #

(Show a, Show b) => Show (Either a b)

Since: base-3.0

Instance details

Defined in Data.Either

Methods

showsPrec :: Int -> Either a b -> ShowS #

show :: Either a b -> String #

showList :: [Either a b] -> ShowS #

HasResolution a => Show (Fixed a)

Since: base-2.1

Instance details

Defined in Data.Fixed

Methods

showsPrec :: Int -> Fixed a -> ShowS #

show :: Fixed a -> String #

showList :: [Fixed a] -> ShowS #

Show (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

showsPrec :: Int -> Proxy s -> ShowS #

show :: Proxy s -> String #

showList :: [Proxy s] -> ShowS #

(Show a, Show b) => Show (Arg a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

showsPrec :: Int -> Arg a b -> ShowS #

show :: Arg a b -> String #

showList :: [Arg a b] -> ShowS #

Show (TypeRep a) 
Instance details

Defined in Data.Typeable.Internal

Methods

showsPrec :: Int -> TypeRep a -> ShowS #

show :: TypeRep a -> String #

showList :: [TypeRep a] -> ShowS #

Show (U1 p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> U1 p -> ShowS #

show :: U1 p -> String #

showList :: [U1 p] -> ShowS #

Show (V1 p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> V1 p -> ShowS #

show :: V1 p -> String #

showList :: [V1 p] -> ShowS #

Show (ST s a)

Since: base-2.1

Instance details

Defined in GHC.ST

Methods

showsPrec :: Int -> ST s a -> ShowS #

show :: ST s a -> String #

showList :: [ST s a] -> ShowS #

Show a => Show (ListN n a) 
Instance details

Defined in Basement.Sized.List

Methods

showsPrec :: Int -> ListN n a -> ShowS #

show :: ListN n a -> String #

showList :: [ListN n a] -> ShowS #

(Show a, Show b) => Show (Bimap a b) 
Instance details

Defined in Data.Bimap

Methods

showsPrec :: Int -> Bimap a b -> ShowS #

show :: Bimap a b -> String #

showList :: [Bimap a b] -> ShowS #

Show (a :- b) 
Instance details

Defined in Data.Constraint

Methods

showsPrec :: Int -> (a :- b) -> ShowS #

show :: (a :- b) -> String #

showList :: [a :- b] -> ShowS #

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

(Show1 f, Show a) => Show (Cofree f a) 
Instance details

Defined in Control.Comonad.Cofree

Methods

showsPrec :: Int -> Cofree f a -> ShowS #

show :: Cofree f a -> String #

showList :: [Cofree f a] -> ShowS #

(Show1 f, Show a) => Show (Free f a) 
Instance details

Defined in Control.Monad.Free

Methods

showsPrec :: Int -> Free f a -> ShowS #

show :: Free f a -> String #

showList :: [Free f a] -> ShowS #

Show k => Show (Extension p k) 
Instance details

Defined in Data.Field.Galois.Extension

Methods

showsPrec :: Int -> Extension p k -> ShowS #

show :: Extension p k -> String #

showList :: [Extension p k] -> ShowS #

Show k => Show (RootsOfUnity n k) 
Instance details

Defined in Data.Field.Galois.Unity

Show (f a) => Show (Yoneda f a) 
Instance details

Defined in Data.Functor.Yoneda

Methods

showsPrec :: Int -> Yoneda f a -> ShowS #

show :: Yoneda f a -> String #

showList :: [Yoneda f a] -> ShowS #

Show (TAddress p vd) Source # 
Instance details

Defined in Lorentz.Address

Methods

showsPrec :: Int -> TAddress p vd -> ShowS #

show :: TAddress p vd -> String #

showList :: [TAddress p vd] -> ShowS #

Show (inp :-> out) Source # 
Instance details

Defined in Lorentz.Base

Methods

showsPrec :: Int -> (inp :-> out) -> ShowS #

show :: (inp :-> out) -> String #

showList :: [inp :-> out] -> ShowS #

Show (ContractCode cp st) Source # 
Instance details

Defined in Lorentz.Base

Methods

showsPrec :: Int -> ContractCode cp st -> ShowS #

show :: ContractCode cp st -> String #

showList :: [ContractCode cp st] -> ShowS #

Show (Hash alg a) Source # 
Instance details

Defined in Lorentz.Bytes

Methods

showsPrec :: Int -> Hash alg a -> ShowS #

show :: Hash alg a -> String #

showList :: [Hash alg a] -> ShowS #

HasResolution a => Show (NFixed a) Source # 
Instance details

Defined in Lorentz.CustomArith.FixedArith

Methods

showsPrec :: Int -> NFixed a -> ShowS #

show :: NFixed a -> String #

showList :: [NFixed a] -> ShowS #

Show (Extensible x) Source # 
Instance details

Defined in Lorentz.Extensible

Show (WrappedLambda i o) Source # 
Instance details

Defined in Lorentz.Lambda

Show a => Show (View_ a r) Source # 
Instance details

Defined in Lorentz.Macro

Methods

showsPrec :: Int -> View_ a r -> ShowS #

show :: View_ a r -> String #

showList :: [View_ a r] -> ShowS #

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

Defined in Lorentz.Macro

Methods

showsPrec :: Int -> Void_ a b -> ShowS #

show :: Void_ a b -> String #

showList :: [Void_ a b] -> ShowS #

(Show a, Show b) => Show (ZippedStackRepr a b) Source # 
Instance details

Defined in Lorentz.Zip

(Show (Token s), Show e) => Show (ParseError s e) 
Instance details

Defined in Text.Megaparsec.Error

Methods

showsPrec :: Int -> ParseError s e -> ShowS #

show :: ParseError s e -> String #

showList :: [ParseError s e] -> ShowS #

(Show s, Show (Token s), Show e) => Show (ParseErrorBundle s e) 
Instance details

Defined in Text.Megaparsec.Error

(Show (ParseError s e), Show s) => Show (State s e) 
Instance details

Defined in Text.Megaparsec.State

Methods

showsPrec :: Int -> State s e -> ShowS #

show :: State s e -> String #

showList :: [State s e] -> ShowS #

(Show n, Show m) => Show (ArithError n m) 
Instance details

Defined in Morley.Michelson.Typed.Arith

Methods

showsPrec :: Int -> ArithError n m -> ShowS #

show :: ArithError n m -> String #

showList :: [ArithError n m] -> ShowS #

Show (EntrypointCallT param arg) 
Instance details

Defined in Morley.Michelson.Typed.Entrypoints

Methods

showsPrec :: Int -> EntrypointCallT param arg -> ShowS #

show :: EntrypointCallT param arg -> String #

showList :: [EntrypointCallT param arg] -> ShowS #

Show (EpLiftSequence arg param) 
Instance details

Defined in Morley.Michelson.Typed.Entrypoints

Methods

showsPrec :: Int -> EpLiftSequence arg param -> ShowS #

show :: EpLiftSequence arg param -> String #

showList :: [EpLiftSequence arg param] -> ShowS #

(Show k, Show v) => Show (BigMap k v) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Methods

showsPrec :: Int -> BigMap k v -> ShowS #

show :: BigMap k v -> String #

showList :: [BigMap k v] -> ShowS #

Show (Instr inp out) 
Instance details

Defined in Morley.Michelson.Typed.Instr

Methods

showsPrec :: Int -> Instr inp out -> ShowS #

show :: Instr inp out -> String #

showList :: [Instr inp out] -> ShowS #

Show (Emit instr t) 
Instance details

Defined in Morley.Michelson.Typed.Value

Methods

showsPrec :: Int -> Emit instr t -> ShowS #

show :: Emit instr t -> String #

showList :: [Emit instr t] -> ShowS #

Show (TransferTokens instr p) 
Instance details

Defined in Morley.Michelson.Typed.Value

Methods

showsPrec :: Int -> TransferTokens instr p -> ShowS #

show :: TransferTokens instr p -> String #

showList :: [TransferTokens instr p] -> ShowS #

Show (Value' instr t) 
Instance details

Defined in Morley.Michelson.Typed.Value

Methods

showsPrec :: Int -> Value' instr t -> ShowS #

show :: Value' instr t -> String #

showList :: [Value' instr t] -> ShowS #

(forall (arg :: T) (ret :: T). Show (ViewCode' instr arg st ret)) => Show (SomeView' instr st) 
Instance details

Defined in Morley.Michelson.Typed.View

Methods

showsPrec :: Int -> SomeView' instr st -> ShowS #

show :: SomeView' instr st -> String #

showList :: [SomeView' instr st] -> ShowS #

(forall (i :: [T]) (o :: [T]). Show (instr i o)) => Show (ViewsSet' instr st) 
Instance details

Defined in Morley.Michelson.Typed.View

Methods

showsPrec :: Int -> ViewsSet' instr st -> ShowS #

show :: ViewsSet' instr st -> String #

showList :: [ViewsSet' instr st] -> ShowS #

Typeable tag => Show (Annotation tag) 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

Methods

showsPrec :: Int -> Annotation tag -> ShowS #

show :: Annotation tag -> String #

showList :: [Annotation tag] -> ShowS #

(Show a, Show b) => Show (Bimap a b) 
Instance details

Defined in Morley.Util.Bimap

Methods

showsPrec :: Int -> Bimap a b -> ShowS #

show :: Bimap a b -> String #

showList :: [Bimap a b] -> ShowS #

Show a => Show (SizedList' n a) 
Instance details

Defined in Morley.Util.SizedList

Methods

showsPrec :: Int -> SizedList' n a -> ShowS #

show :: SizedList' n a -> String #

showList :: [SizedList' n a] -> ShowS #

(forall (a :: k). Show (f a)) => Show (Some1 f) 
Instance details

Defined in Morley.Util.Type

Methods

showsPrec :: Int -> Some1 f -> ShowS #

show :: Some1 f -> String #

showList :: [Some1 f] -> ShowS #

(Show a, Vector v a) => Show (Poly v a) 
Instance details

Defined in Data.Poly.Internal.Dense

Methods

showsPrec :: Int -> Poly v a -> ShowS #

show :: Poly v a -> String #

showList :: [Poly v a] -> ShowS #

Show v => Show (IntMapOf k v) 
Instance details

Defined in Data.Semiring

Methods

showsPrec :: Int -> IntMapOf k v -> ShowS #

show :: IntMapOf k v -> String #

showList :: [IntMapOf k v] -> ShowS #

ShowSing (Maybe a) => Show (SFirst z) 
Instance details

Defined in Data.Monoid.Singletons

Methods

showsPrec :: Int -> SFirst z -> ShowS #

show :: SFirst z -> String #

showList :: [SFirst z] -> ShowS #

ShowSing (Maybe a) => Show (SLast z) 
Instance details

Defined in Data.Monoid.Singletons

Methods

showsPrec :: Int -> SLast z -> ShowS #

show :: SLast z -> String #

showList :: [SLast z] -> ShowS #

ShowSing a => Show (SIdentity z) 
Instance details

Defined in Data.Singletons.Base.Instances

(ShowSing a, ShowSing [a]) => Show (SList z) 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

showsPrec :: Int -> SList z -> ShowS #

show :: SList z -> String #

showList :: [SList z] -> ShowS #

ShowSing a => Show (SMaybe z) 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

showsPrec :: Int -> SMaybe z -> ShowS #

show :: SMaybe z -> String #

showList :: [SMaybe z] -> ShowS #

(ShowSing a, ShowSing [a]) => Show (SNonEmpty z) 
Instance details

Defined in Data.Singletons.Base.Instances

GShow tag => Show (Some tag) 
Instance details

Defined in Data.GADT.Internal

Methods

showsPrec :: Int -> Some tag -> ShowS #

show :: Some tag -> String #

showList :: [Some tag] -> ShowS #

(Show a, Show b) => Show (Either a b) 
Instance details

Defined in Data.Strict.Either

Methods

showsPrec :: Int -> Either a b -> ShowS #

show :: Either a b -> String #

showList :: [Either a b] -> ShowS #

(Show a, Show b) => Show (These a b) 
Instance details

Defined in Data.Strict.These

Methods

showsPrec :: Int -> These a b -> ShowS #

show :: These a b -> String #

showList :: [These a b] -> ShowS #

(Show a, Show b) => Show (Pair a b) 
Instance details

Defined in Data.Strict.Tuple

Methods

showsPrec :: Int -> Pair a b -> ShowS #

show :: Pair a b -> String #

showList :: [Pair a b] -> ShowS #

(Show a, Show b) => Show (These a b) 
Instance details

Defined in Data.These

Methods

showsPrec :: Int -> These a b -> ShowS #

show :: These a b -> String #

showList :: [These a b] -> ShowS #

(Show1 m, Show a) => Show (MaybeT m a) 
Instance details

Defined in Control.Monad.Trans.Maybe

Methods

showsPrec :: Int -> MaybeT m a -> ShowS #

show :: MaybeT m a -> String #

showList :: [MaybeT m a] -> ShowS #

(Show k, Show v) => Show (HashMap k v) 
Instance details

Defined in Data.HashMap.Internal

Methods

showsPrec :: Int -> HashMap k v -> ShowS #

show :: HashMap k v -> String #

showList :: [HashMap k v] -> ShowS #

(Show a, Show b) => Show (a, b)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b) -> ShowS #

show :: (a, b) -> String #

showList :: [(a, b)] -> ShowS #

(Integral a, Show a) :=> (Show (Ratio a)) 
Instance details

Defined in Data.Constraint

Methods

ins :: (Integral a, Show a) :- Show (Ratio a) #

(Show a, Show b) :=> (Show (Either a b)) 
Instance details

Defined in Data.Constraint

Methods

ins :: (Show a, Show b) :- Show (Either a b) #

(Show a, Show b) :=> (Show (a, b)) 
Instance details

Defined in Data.Constraint

Methods

ins :: (Show a, Show b) :- Show (a, b) #

Show a => Show (Const a b)

This instance would be equivalent to the derived instances of the Const newtype if the getConst field were removed

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Const

Methods

showsPrec :: Int -> Const a b -> ShowS #

show :: Const a b -> String #

showList :: [Const a b] -> ShowS #

Show (f a) => Show (Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

showsPrec :: Int -> Ap f a -> ShowS #

show :: Ap f a -> String #

showList :: [Ap f a] -> ShowS #

Show (f a) => Show (Alt f a)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

showsPrec :: Int -> Alt f a -> ShowS #

show :: Alt f a -> String #

showList :: [Alt f a] -> ShowS #

Show (a :~: b)

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Equality

Methods

showsPrec :: Int -> (a :~: b) -> ShowS #

show :: (a :~: b) -> String #

showList :: [a :~: b] -> ShowS #

Show (f p) => Show (Rec1 f p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> Rec1 f p -> ShowS #

show :: Rec1 f p -> String #

showList :: [Rec1 f p] -> ShowS #

Show (URec Char p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> URec Char p -> ShowS #

show :: URec Char p -> String #

showList :: [URec Char p] -> ShowS #

Show (URec Double p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> URec Double p -> ShowS #

show :: URec Double p -> String #

showList :: [URec Double p] -> ShowS #

Show (URec Float p) 
Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> URec Float p -> ShowS #

show :: URec Float p -> String #

showList :: [URec Float p] -> ShowS #

Show (URec Int p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> URec Int p -> ShowS #

show :: URec Int p -> String #

showList :: [URec Int p] -> ShowS #

Show (URec Word p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> URec Word p -> ShowS #

show :: URec Word p -> String #

showList :: [URec Word p] -> ShowS #

Show (p (Fix p a) a) => Show (Fix p a) 
Instance details

Defined in Data.Bifunctor.Fix

Methods

showsPrec :: Int -> Fix p a -> ShowS #

show :: Fix p a -> String #

showList :: [Fix p a] -> ShowS #

Show (p a a) => Show (Join p a) 
Instance details

Defined in Data.Bifunctor.Join

Methods

showsPrec :: Int -> Join p a -> ShowS #

show :: Join p a -> String #

showList :: [Join p a] -> ShowS #

(Show a, Show (f b)) => Show (CofreeF f a b) 
Instance details

Defined in Control.Comonad.Trans.Cofree

Methods

showsPrec :: Int -> CofreeF f a b -> ShowS #

show :: CofreeF f a b -> String #

showList :: [CofreeF f a b] -> ShowS #

Show (w (CofreeF f a (CofreeT f w a))) => Show (CofreeT f w a) 
Instance details

Defined in Control.Comonad.Trans.Cofree

Methods

showsPrec :: Int -> CofreeT f w a -> ShowS #

show :: CofreeT f w a -> String #

showList :: [CofreeT f w a] -> ShowS #

(Show a, Show (f b)) => Show (FreeF f a b) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

showsPrec :: Int -> FreeF f a b -> ShowS #

show :: FreeF f a b -> String #

showList :: [FreeF f a b] -> ShowS #

(Show1 f, Show1 m, Show a) => Show (FreeT f m a) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

showsPrec :: Int -> FreeT f m a -> ShowS #

show :: FreeT f m a -> String #

showList :: [FreeT f m a] -> ShowS #

Show (Contract cp st vd) Source # 
Instance details

Defined in Lorentz.Base

Methods

showsPrec :: Int -> Contract cp st vd -> ShowS #

show :: Contract cp st vd -> String #

showList :: [Contract cp st vd] -> ShowS #

(forall (i :: [T]) (o :: [T]). Show (instr i o)) => Show (Contract' instr cp st) 
Instance details

Defined in Morley.Michelson.Typed.Contract

Methods

showsPrec :: Int -> Contract' instr cp st -> ShowS #

show :: Contract' instr cp st -> String #

showList :: [Contract' instr cp st] -> ShowS #

Show (instr (ContractInp cp st) (ContractOut st)) => Show (ContractCode' instr cp st) 
Instance details

Defined in Morley.Michelson.Typed.Contract

Methods

showsPrec :: Int -> ContractCode' instr cp st -> ShowS #

show :: ContractCode' instr cp st -> String #

showList :: [ContractCode' instr cp st] -> ShowS #

Show (CreateContract instr cp st) 
Instance details

Defined in Morley.Michelson.Typed.Value

Methods

showsPrec :: Int -> CreateContract instr cp st -> ShowS #

show :: CreateContract instr cp st -> String #

showList :: [CreateContract instr cp st] -> ShowS #

Show (LambdaCode' instr inp out) 
Instance details

Defined in Morley.Michelson.Typed.Value

Methods

showsPrec :: Int -> LambdaCode' instr inp out -> ShowS #

show :: LambdaCode' instr inp out -> String #

showList :: [LambdaCode' instr inp out] -> ShowS #

(forall (a :: k). c a => Show (f a)) => Show (Constrained c f) 
Instance details

Defined in Morley.Util.Constrained

Methods

showsPrec :: Int -> Constrained c f -> ShowS #

show :: Constrained c f -> String #

showList :: [Constrained c f] -> ShowS #

Show (SProxy z) 
Instance details

Defined in Data.Proxy.Singletons

Methods

showsPrec :: Int -> SProxy z -> ShowS #

show :: SProxy z -> String #

showList :: [SProxy z] -> ShowS #

(ShowSing a, ShowSing b) => Show (SArg z) 
Instance details

Defined in Data.Semigroup.Singletons

Methods

showsPrec :: Int -> SArg z -> ShowS #

show :: SArg z -> String #

showList :: [SArg z] -> ShowS #

(ShowSing a, ShowSing b) => Show (SEither z) 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

showsPrec :: Int -> SEither z -> ShowS #

show :: SEither z -> String #

showList :: [SEither z] -> ShowS #

(ShowSing a, ShowSing b) => Show (STuple2 z) 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

showsPrec :: Int -> STuple2 z -> ShowS #

show :: STuple2 z -> String #

showList :: [STuple2 z] -> ShowS #

Show (GOrdering a b) 
Instance details

Defined in Data.GADT.Internal

Methods

showsPrec :: Int -> GOrdering a b -> ShowS #

show :: GOrdering a b -> String #

showList :: [GOrdering a b] -> ShowS #

Show b => Show (Tagged s b) 
Instance details

Defined in Data.Tagged

Methods

showsPrec :: Int -> Tagged s b -> ShowS #

show :: Tagged s b -> String #

showList :: [Tagged s b] -> ShowS #

(Show1 f, Show1 g, Show a) => Show (These1 f g a) 
Instance details

Defined in Data.Functor.These

Methods

showsPrec :: Int -> These1 f g a -> ShowS #

show :: These1 f g a -> String #

showList :: [These1 f g a] -> ShowS #

(Show e, Show1 m, Show a) => Show (ErrorT e m a) 
Instance details

Defined in Control.Monad.Trans.Error

Methods

showsPrec :: Int -> ErrorT e m a -> ShowS #

show :: ErrorT e m a -> String #

showList :: [ErrorT e m a] -> ShowS #

(Show e, Show1 m, Show a) => Show (ExceptT e m a) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

showsPrec :: Int -> ExceptT e m a -> ShowS #

show :: ExceptT e m a -> String #

showList :: [ExceptT e m a] -> ShowS #

(Show1 f, Show a) => Show (IdentityT f a) 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

showsPrec :: Int -> IdentityT f a -> ShowS #

show :: IdentityT f a -> String #

showList :: [IdentityT f a] -> ShowS #

(RPureConstrained (IndexableField rs) rs, RecApplicative rs, Show (Rec f rs)) => Show (ARec f rs) 
Instance details

Defined in Data.Vinyl.ARec.Internal

Methods

showsPrec :: Int -> ARec f rs -> ShowS #

show :: ARec f rs -> String #

showList :: [ARec f rs] -> ShowS #

(RMap rs, ReifyConstraint Show f rs, RecordToList rs) => Show (Rec f rs)

Records may be shown insofar as their points may be shown. reifyConstraint is used to great effect here.

Instance details

Defined in Data.Vinyl.Core

Methods

showsPrec :: Int -> Rec f rs -> ShowS #

show :: Rec f rs -> String #

showList :: [Rec f rs] -> ShowS #

Show a => Show (Const a b) 
Instance details

Defined in Data.Vinyl.Functor

Methods

showsPrec :: Int -> Const a b -> ShowS #

show :: Const a b -> String #

showList :: [Const a b] -> ShowS #

(Show a, Show b, Show c) => Show (a, b, c)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c) -> ShowS #

show :: (a, b, c) -> String #

showList :: [(a, b, c)] -> ShowS #

(Show1 f, Show1 g, Show a) => Show (Product f g a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Product

Methods

showsPrec :: Int -> Product f g a -> ShowS #

show :: Product f g a -> String #

showList :: [Product f g a] -> ShowS #

(Show1 f, Show1 g, Show a) => Show (Sum f g a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Sum

Methods

showsPrec :: Int -> Sum f g a -> ShowS #

show :: Sum f g a -> String #

showList :: [Sum f g a] -> ShowS #

Show (a :~~: b)

Since: base-4.10.0.0

Instance details

Defined in Data.Type.Equality

Methods

showsPrec :: Int -> (a :~~: b) -> ShowS #

show :: (a :~~: b) -> String #

showList :: [a :~~: b] -> ShowS #

(Show (f p), Show (g p)) => Show ((f :*: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> (f :*: g) p -> ShowS #

show :: (f :*: g) p -> String #

showList :: [(f :*: g) p] -> ShowS #

(Show (f p), Show (g p)) => Show ((f :+: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> (f :+: g) p -> ShowS #

show :: (f :+: g) p -> String #

showList :: [(f :+: g) p] -> ShowS #

Show c => Show (K1 i c p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> K1 i c p -> ShowS #

show :: K1 i c p -> String #

showList :: [K1 i c p] -> ShowS #

Show (BigMapId k2 v) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Methods

showsPrec :: Int -> BigMapId k2 v -> ShowS #

show :: BigMapId k2 v -> String #

showList :: [BigMapId k2 v] -> ShowS #

(forall (o' :: k). Show (instr i o')) => Show (RemFail instr i o) 
Instance details

Defined in Morley.Michelson.Typed.Value

Methods

showsPrec :: Int -> RemFail instr i o -> ShowS #

show :: RemFail instr i o -> String #

showList :: [RemFail instr i o] -> ShowS #

Show (ViewCode' instr arg st ret) => Show (View' instr arg st ret) 
Instance details

Defined in Morley.Michelson.Typed.View

Methods

showsPrec :: Int -> View' instr arg st ret -> ShowS #

show :: View' instr arg st ret -> String #

showList :: [View' instr arg st ret] -> ShowS #

(ShowSing a, ShowSing b, ShowSing c) => Show (STuple3 z) 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

showsPrec :: Int -> STuple3 z -> ShowS #

show :: STuple3 z -> String #

showList :: [STuple3 z] -> ShowS #

(Show a, Show b, Show c, Show d) => Show (a, b, c, d)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d) -> ShowS #

show :: (a, b, c, d) -> String #

showList :: [(a, b, c, d)] -> ShowS #

(Show1 f, Show1 g, Show a) => Show (Compose f g a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Compose

Methods

showsPrec :: Int -> Compose f g a -> ShowS #

show :: Compose f g a -> String #

showList :: [Compose f g a] -> ShowS #

Show (f (g p)) => Show ((f :.: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> (f :.: g) p -> ShowS #

show :: (f :.: g) p -> String #

showList :: [(f :.: g) p] -> ShowS #

Show (f p) => Show (M1 i c f p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> M1 i c f p -> ShowS #

show :: M1 i c f p -> String #

showList :: [M1 i c f p] -> ShowS #

Show (f a) => Show (Clown f a b) 
Instance details

Defined in Data.Bifunctor.Clown

Methods

showsPrec :: Int -> Clown f a b -> ShowS #

show :: Clown f a b -> String #

showList :: [Clown f a b] -> ShowS #

Show (p b a) => Show (Flip p a b) 
Instance details

Defined in Data.Bifunctor.Flip

Methods

showsPrec :: Int -> Flip p a b -> ShowS #

show :: Flip p a b -> String #

showList :: [Flip p a b] -> ShowS #

Show (g b) => Show (Joker g a b) 
Instance details

Defined in Data.Bifunctor.Joker

Methods

showsPrec :: Int -> Joker g a b -> ShowS #

show :: Joker g a b -> String #

showList :: [Joker g a b] -> ShowS #

Show (p a b) => Show (WrappedBifunctor p a b) 
Instance details

Defined in Data.Bifunctor.Wrapped

(ShowSing a, ShowSing b, ShowSing c, ShowSing d) => Show (STuple4 z) 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

showsPrec :: Int -> STuple4 z -> ShowS #

show :: STuple4 z -> String #

showList :: [STuple4 z] -> ShowS #

Show (f (g a)) => Show (Compose f g a) 
Instance details

Defined in Data.Vinyl.Functor

Methods

showsPrec :: Int -> Compose f g a -> ShowS #

show :: Compose f g a -> String #

showList :: [Compose f g a] -> ShowS #

(Show a, Show b, Show c, Show d, Show e) => Show (a, b, c, d, e)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e) -> ShowS #

show :: (a, b, c, d, e) -> String #

showList :: [(a, b, c, d, e)] -> ShowS #

(Show (f a b), Show (g a b)) => Show (Product f g a b) 
Instance details

Defined in Data.Bifunctor.Product

Methods

showsPrec :: Int -> Product f g a b -> ShowS #

show :: Product f g a b -> String #

showList :: [Product f g a b] -> ShowS #

(Show (p a b), Show (q a b)) => Show (Sum p q a b) 
Instance details

Defined in Data.Bifunctor.Sum

Methods

showsPrec :: Int -> Sum p q a b -> ShowS #

show :: Sum p q a b -> String #

showList :: [Sum p q a b] -> ShowS #

(ShowSing a, ShowSing b, ShowSing c, ShowSing d, ShowSing e) => Show (STuple5 z) 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

showsPrec :: Int -> STuple5 z -> ShowS #

show :: STuple5 z -> String #

showList :: [STuple5 z] -> ShowS #

(Show a, Show b, Show c, Show d, Show e, Show f) => Show (a, b, c, d, e, f)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f) -> ShowS #

show :: (a, b, c, d, e, f) -> String #

showList :: [(a, b, c, d, e, f)] -> ShowS #

Show (f (p a b)) => Show (Tannen f p a b) 
Instance details

Defined in Data.Bifunctor.Tannen

Methods

showsPrec :: Int -> Tannen f p a b -> ShowS #

show :: Tannen f p a b -> String #

showList :: [Tannen f p a b] -> ShowS #

(ShowSing a, ShowSing b, ShowSing c, ShowSing d, ShowSing e, ShowSing f) => Show (STuple6 z) 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

showsPrec :: Int -> STuple6 z -> ShowS #

show :: STuple6 z -> String #

showList :: [STuple6 z] -> ShowS #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g) => Show (a, b, c, d, e, f, g)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g) -> ShowS #

show :: (a, b, c, d, e, f, g) -> String #

showList :: [(a, b, c, d, e, f, g)] -> ShowS #

(ShowSing a, ShowSing b, ShowSing c, ShowSing d, ShowSing e, ShowSing f, ShowSing g) => Show (STuple7 z) 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

showsPrec :: Int -> STuple7 z -> ShowS #

show :: STuple7 z -> String #

showList :: [STuple7 z] -> ShowS #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h) => Show (a, b, c, d, e, f, g, h)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h) -> ShowS #

show :: (a, b, c, d, e, f, g, h) -> String #

showList :: [(a, b, c, d, e, f, g, h)] -> ShowS #

Show (p (f a) (g b)) => Show (Biff p f g a b) 
Instance details

Defined in Data.Bifunctor.Biff

Methods

showsPrec :: Int -> Biff p f g a b -> ShowS #

show :: Biff p f g a b -> String #

showList :: [Biff p f g a b] -> ShowS #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i) => Show (a, b, c, d, e, f, g, h, i)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i) -> ShowS #

show :: (a, b, c, d, e, f, g, h, i) -> String #

showList :: [(a, b, c, d, e, f, g, h, i)] -> ShowS #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j) => Show (a, b, c, d, e, f, g, h, i, j)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j) -> ShowS #

show :: (a, b, c, d, e, f, g, h, i, j) -> String #

showList :: [(a, b, c, d, e, f, g, h, i, j)] -> ShowS #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k) => Show (a, b, c, d, e, f, g, h, i, j, k)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k) -> ShowS #

show :: (a, b, c, d, e, f, g, h, i, j, k) -> String #

showList :: [(a, b, c, d, e, f, g, h, i, j, k)] -> ShowS #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l) => Show (a, b, c, d, e, f, g, h, i, j, k, l)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k, l) -> ShowS #

show :: (a, b, c, d, e, f, g, h, i, j, k, l) -> String #

showList :: [(a, b, c, d, e, f, g, h, i, j, k, l)] -> ShowS #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m) => Show (a, b, c, d, e, f, g, h, i, j, k, l, m)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> ShowS #

show :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> String #

showList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m)] -> ShowS #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m, Show n) => Show (a, b, c, d, e, f, g, h, i, j, k, l, m, n)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> ShowS #

show :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> String #

showList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] -> ShowS #

(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m, Show n, Show o) => Show (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> ShowS #

show :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> String #

showList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)] -> ShowS #

class Default a where #

A class for types with a default value.

Minimal complete definition

Nothing

Methods

def :: a #

The default value for this type.

Instances

Instances details
Default All 
Instance details

Defined in Data.Default.Class

Methods

def :: All #

Default Any 
Instance details

Defined in Data.Default.Class

Methods

def :: Any #

Default CClock 
Instance details

Defined in Data.Default.Class

Methods

def :: CClock #

Default CDouble 
Instance details

Defined in Data.Default.Class

Methods

def :: CDouble #

Default CFloat 
Instance details

Defined in Data.Default.Class

Methods

def :: CFloat #

Default CInt 
Instance details

Defined in Data.Default.Class

Methods

def :: CInt #

Default CIntMax 
Instance details

Defined in Data.Default.Class

Methods

def :: CIntMax #

Default CIntPtr 
Instance details

Defined in Data.Default.Class

Methods

def :: CIntPtr #

Default CLLong 
Instance details

Defined in Data.Default.Class

Methods

def :: CLLong #

Default CLong 
Instance details

Defined in Data.Default.Class

Methods

def :: CLong #

Default CPtrdiff 
Instance details

Defined in Data.Default.Class

Methods

def :: CPtrdiff #

Default CSUSeconds 
Instance details

Defined in Data.Default.Class

Methods

def :: CSUSeconds #

Default CShort 
Instance details

Defined in Data.Default.Class

Methods

def :: CShort #

Default CSigAtomic 
Instance details

Defined in Data.Default.Class

Methods

def :: CSigAtomic #

Default CSize 
Instance details

Defined in Data.Default.Class

Methods

def :: CSize #

Default CTime 
Instance details

Defined in Data.Default.Class

Methods

def :: CTime #

Default CUInt 
Instance details

Defined in Data.Default.Class

Methods

def :: CUInt #

Default CUIntMax 
Instance details

Defined in Data.Default.Class

Methods

def :: CUIntMax #

Default CUIntPtr 
Instance details

Defined in Data.Default.Class

Methods

def :: CUIntPtr #

Default CULLong 
Instance details

Defined in Data.Default.Class

Methods

def :: CULLong #

Default CULong 
Instance details

Defined in Data.Default.Class

Methods

def :: CULong #

Default CUSeconds 
Instance details

Defined in Data.Default.Class

Methods

def :: CUSeconds #

Default CUShort 
Instance details

Defined in Data.Default.Class

Methods

def :: CUShort #

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

Defined in Data.Default.Class

Methods

def :: Int8 #

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

Defined in Data.Default.Class

Methods

def :: Ordering #

Default DeriveRPCOptions 
Instance details

Defined in Morley.AsRPC

Methods

def :: DeriveRPCOptions #

Default ErrorSrcPos 
Instance details

Defined in Morley.Michelson.ErrorPos

Methods

def :: ErrorSrcPos #

Default Pos 
Instance details

Defined in Morley.Michelson.ErrorPos

Methods

def :: Pos #

Default SrcPos 
Instance details

Defined in Morley.Michelson.ErrorPos

Methods

def :: SrcPos #

Default MorleyLogsBuilder 
Instance details

Defined in Morley.Michelson.Interpret

Methods

def :: MorleyLogsBuilder #

Default OptimizerConf 
Instance details

Defined in Morley.Michelson.Optimizer

Methods

def :: OptimizerConf #

Default TypeCheckInstrEnv 
Instance details

Defined in Morley.Michelson.TypeCheck.TypeCheck

Methods

def :: TypeCheckInstrEnv #

Default TypeCheckOptions 
Instance details

Defined in Morley.Michelson.TypeCheck.TypeCheck

Methods

def :: TypeCheckOptions #

Default EntriesOrder 
Instance details

Defined in Morley.Michelson.Untyped.Contract

Methods

def :: EntriesOrder #

Default Word8 
Instance details

Defined in Data.Default.Class

Methods

def :: Word8 #

Default Integer 
Instance details

Defined in Data.Default.Class

Methods

def :: Integer #

Default () 
Instance details

Defined in Data.Default.Class

Methods

def :: () #

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

Defined in Data.Default.Class

Methods

def :: Word #

(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 (Product a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Product a #

Num a => Default (Sum a) 
Instance details

Defined in Data.Default.Class

Methods

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

(SingI t, Default (Anns xs)) => Default (Anns (Notes t ': xs)) 
Instance details

Defined in Morley.Michelson.Typed.Annotation

Methods

def :: Anns (Notes t ': xs) #

(Typeable tag, Default (Anns xs)) => Default (Anns (Annotation tag ': xs)) 
Instance details

Defined in Morley.Michelson.Typed.Annotation

Methods

def :: Anns (Annotation tag ': xs) #

Default (Anns ('[] :: [Type])) 
Instance details

Defined in Morley.Michelson.Typed.Annotation

Methods

def :: Anns '[] #

Applicative x => Default (DfsSettings x) 
Instance details

Defined in Morley.Michelson.Typed.Util

Methods

def :: DfsSettings x #

Default (Maybe a) 
Instance details

Defined in Data.Default.Class

Methods

def :: Maybe a #

Default [a] 
Instance details

Defined in Data.Default.Class

Methods

def :: [a] #

Default (BigMap k v) 
Instance details

Defined in Morley.Michelson.Typed.Haskell.Value

Methods

def :: BigMap k v #

Default (ViewsSet' instr st) 
Instance details

Defined in Morley.Michelson.Typed.View

Methods

def :: ViewsSet' instr st #

Default (Annotation tag) 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

Methods

def :: Annotation tag #

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 a, Default b, Default c) => Default (a, b, c) 
Instance details

Defined in Data.Default.Class

Methods

def :: (a, b, c) #

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

Defined in Data.Default.Class

Methods

def :: (a, b, c, d) #

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

Defined in Data.Default.Class

Methods

def :: (a, b, c, d, e) #

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

Defined in Data.Default.Class

Methods

def :: (a, b, c, d, e, f) #

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

Defined in Data.Default.Class

Methods

def :: (a, b, c, d, e, f, g) #

data Label (name :: Symbol) where #

Constructors

Label :: forall (name :: Symbol). KnownSymbol name => Label name 

Instances

Instances details
(KnownSymbol name, s ~ name) => IsLabel s (Label name) 
Instance details

Defined in Morley.Util.Label

Methods

fromLabel :: Label name #

Show (Label name) 
Instance details

Defined in Morley.Util.Label

Methods

showsPrec :: Int -> Label name -> ShowS #

show :: Label name -> String #

showList :: [Label name] -> ShowS #

Buildable (Label name) 
Instance details

Defined in Morley.Util.Label

Methods

build :: Label name -> Builder #

Eq (Label name) 
Instance details

Defined in Morley.Util.Label

Methods

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

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

newtype PrintAsValue a Source #

Provides Buildable instance that prints Lorentz value via Michelson's Value.

Result won't be very pretty, but this avoids requiring Show or Buildable instances.

Constructors

PrintAsValue a 

Instances

Instances details
NiceUntypedValue a => Buildable (PrintAsValue a) Source # 
Instance details

Defined in Lorentz.Value

Methods

build :: PrintAsValue a -> Builder #

Re-exports