| Copyright | (C) 2016-2017 Ryan Scott |
|---|---|
| License | BSD-style (see the file LICENSE) |
| Maintainer | Ryan Scott |
| Stability | Provisional |
| Portability | GHC |
| Safe Haskell | Trustworthy |
| Language | Haskell2010 |
Data.Proxyless
Contents
Description
Remove the Proxy, Proxy#, and undefined arguments from functions with
proxyless, proxyHashless, and undefinedless, respectively, which produce
functions that take type information via GHC's -XTypeApplications extension.
This module is only available with GHC 8.0 or later.
Since: 0.2
- proxyless :: forall k a b. (Proxy a -> b) -> b
- proxyHashless :: forall k a b. (Proxy# a -> b) -> b
- undefinedless :: forall a b. (a -> b) -> b
- theBitSize :: forall a. Bits a => Int
- theIsSigned :: forall a. Bits a => Bool
- theBitSizeMaybe :: forall a. Bits a => Maybe Int
- theFiniteBitSize :: forall a. FiniteBits a => Int
- theDataTypeOf :: forall a. Data a => DataType
- theTypeNatTypeRep :: forall a. KnownNat a => TypeRep
- theTypeRep :: forall k a. Typeable a => TypeRep
- theTypeRep# :: forall k a. Typeable a => TypeRep
- theTypeSymbolTypeRep :: forall a. KnownSymbol a => TypeRep
- theSizeOf :: forall a. Storable a => Int
- theAlignment :: forall a. Storable a => Int
- theDatatypeName :: forall k d. Datatype d => [Char]
- theModuleName :: forall k d. Datatype d => [Char]
- theIsNewtype :: forall k d. Datatype d => Bool
- thePackageName :: forall k d. Datatype d => [Char]
- theConName :: forall k c. Constructor c => [Char]
- theConFixity :: forall k c. Constructor c => Fixity
- theConIsRecord :: forall k c. Constructor c => Bool
- theSelName :: forall k s. Selector s => [Char]
- theSelSourceUnpackedness :: forall k s. Selector s => SourceUnpackedness
- theSelSourceStrictness :: forall k s. Selector s => SourceStrictness
- theSelDecidedStrictness :: forall k s. Selector s => DecidedStrictness
- theFromLabel :: forall x a. IsLabel x a => a
- theNatVal :: forall n. KnownNat n => Integer
- theNatVal' :: forall n. KnownNat n => Integer
- theSameNat :: forall a b. (KnownNat a, KnownNat b) => Maybe (a :~: b)
- theSameSymbol :: forall a b. (KnownSymbol a, KnownSymbol b) => Maybe (a :~: b)
- theSomeNat :: forall n. KnownNat n => SomeNat
- theSomeSymbol :: forall n. KnownSymbol n => SomeSymbol
- theSymbolVal :: forall n. KnownSymbol n => String
- theSymbolVal' :: forall n. KnownSymbol n => String
- theFloatRadix :: forall a. RealFloat a => Integer
- theFloatDigits :: forall a. RealFloat a => Int
- theFloatRange :: forall a. RealFloat a => (Int, Int)
- theParseFormat :: forall a. PrintfArg a => ModifierParser
proxyless, proxyHashless, and undefinedless
proxyless :: forall k a b. (Proxy a -> b) -> b Source #
Converts a constant function that takes a Proxy argument to one that
doesn't require an argument.
Since: 0.2
proxyHashless :: forall k a b. (Proxy# a -> b) -> b Source #
Converts a constant function that takes a Proxy# argument to one that
doesn't require an argument.
Since: 0.2
undefinedless :: forall a b. (a -> b) -> b Source #
Converts a constant function that takes an undefined argument to one that
doesn't require an argument.
Since: 0.2
Proxyless functions
Data.Bits
theBitSize :: forall a. Bits a => Int Source #
theBitSize=undefinedlessbitSize
Since: 0.2
theIsSigned :: forall a. Bits a => Bool Source #
theIsSigned=undefinedlessisSigned
Since: 0.2
theBitSizeMaybe :: forall a. Bits a => Maybe Int Source #
theBitSizeMaybe=undefinedlessbitSizeMaybe
Since: 0.2
theFiniteBitSize :: forall a. FiniteBits a => Int Source #
theFiniteBitSize=undefinedlessfiniteBitSize
Since: 0.2
Data.Data
theDataTypeOf :: forall a. Data a => DataType Source #
theDataTypeOf=undefinedlessdataTypeOf
Since: 0.2
Data.Typeable
theTypeNatTypeRep :: forall a. KnownNat a => TypeRep Source #
theTypeNatTypeRep=proxyHashlesstypeNatTypeRep
Note that in base-4.10 and later, theTypeNatTypeRep is simply a synonym
for theTypeRep, as typeNatTypeRep is no longer exported.
Since: 0.2
theTypeRep :: forall k a. Typeable a => TypeRep Source #
theTypeRep=proxylesstypeRep
Since: 0.2
theTypeRep# :: forall k a. Typeable a => TypeRep Source #
theTypeRep#=proxyHashlesstypeRep#
Note that in base-4.10 and later, theTypeRep# is simply a synonym for
theTypeRep, as typeRep# is no longer exported.
Since: 0.2
theTypeSymbolTypeRep :: forall a. KnownSymbol a => TypeRep Source #
theTypeSymbolTypeRep=proxyHashlesstypeSymbolTypeRep
Note that in base-4.10 and later, theTypeSymbolTypeRep is simply a
synonym for theTypeRep, as typeSymbolTypeRep is no longer exported.
Since: 0.2
Foreign.Storable
theAlignment :: forall a. Storable a => Int Source #
theAlignment=undefinedlessalignment
Since: 0.2
GHC.Generics
theDatatypeName :: forall k d. Datatype d => [Char] Source #
theDatatypeName=datatypeNameundefined
Since: 0.2
theModuleName :: forall k d. Datatype d => [Char] Source #
theModuleName=moduleNameundefined
Since: 0.2
theIsNewtype :: forall k d. Datatype d => Bool Source #
theIsNewtype=isNewtypeundefined
Since: 0.2
thePackageName :: forall k d. Datatype d => [Char] Source #
thePackageName=packageNameundefined
Since: 0.2
theConName :: forall k c. Constructor c => [Char] Source #
theConName=conNameundefined
Since: 0.2
theConFixity :: forall k c. Constructor c => Fixity Source #
theConFixity=conFixityundefined
Since: 0.2
theConIsRecord :: forall k c. Constructor c => Bool Source #
theConIsRecord=conIsRecordundefined
Since: 0.2
theSelName :: forall k s. Selector s => [Char] Source #
theSelName=selNameundefined
Since: 0.2
theSelSourceUnpackedness :: forall k s. Selector s => SourceUnpackedness Source #
theSelSourceUnpackedness=selSourceUnpackednessundefined
Since: 0.2
theSelSourceStrictness :: forall k s. Selector s => SourceStrictness Source #
theSelSourceStrictness=selSourceStrictnessundefined
Since: 0.2
theSelDecidedStrictness :: forall k s. Selector s => DecidedStrictness Source #
theSelDecidedStrictness=selDecidedStrictnessundefined
Since: 0.2
GHC.OverloadedLabels
theFromLabel :: forall x a. IsLabel x a => a Source #
In base-4.10 and later, this is simply a synonym for fromLabel.
In base-4.9, theFromLabel is defined as:
theFromLabel=proxyHashlessfromLabel
Since: 0.2
GHC.TypeLits
theNatVal' :: forall n. KnownNat n => Integer Source #
theNatVal'=proxyHashlessnatVal'
Since: 0.2
theSameNat :: forall a b. (KnownNat a, KnownNat b) => Maybe (a :~: b) Source #
theSameNat=sameNatProxyProxy
Since: 0.2
theSameSymbol :: forall a b. (KnownSymbol a, KnownSymbol b) => Maybe (a :~: b) Source #
theSameSymbol=sameSymbolProxyProxy
Since: 0.2
theSomeNat :: forall n. KnownNat n => SomeNat Source #
theSomeNat=proxylessSomeNat
Since: 0.2
theSomeSymbol :: forall n. KnownSymbol n => SomeSymbol Source #
theSomeSymbol=proxylessSomeSymbol
Since: 0.2
theSymbolVal :: forall n. KnownSymbol n => String Source #
theSymbolVal=proxylesssymbolVal
Since: 0.2
theSymbolVal' :: forall n. KnownSymbol n => String Source #
theSymbolVal'=proxyHashlesssymbolVal'
Since: 0.2
Prelude
theFloatRadix :: forall a. RealFloat a => Integer Source #
theFloatRadix=undefinedlessfloatRadix
Since: 0.2
theFloatDigits :: forall a. RealFloat a => Int Source #
theFloatDigits=undefinedlessfloatDigits
Since: 0.2
theFloatRange :: forall a. RealFloat a => (Int, Int) Source #
theFloatRange=undefinedlessfloatRange
Since: 0.2
Text.Printf
theParseFormat :: forall a. PrintfArg a => ModifierParser Source #
theParseFormat=undefinedlessparseFormat
Since: 0.2