| Copyright | (C) 2016 Ryan Scott |
|---|---|
| License | BSD-style (see the file LICENSE) |
| Maintainer | Ryan Scott |
| Stability | Provisional |
| Portability | GHC |
| Safe Haskell | Safe |
| Language | Haskell2010 |
Data.Proxied
Contents
- proxied :: (a -> b) -> proxy a -> b
- unproxied :: (Proxy a -> b) -> a -> b
- module Data.Proxy
- bitSizeProxied :: Bits a => proxy a -> Int
- isSignedProxied :: Bits a => proxy a -> Bool
- bitSizeMaybeProxied :: Bits a => proxy a -> Maybe Int
- finiteBitSizeProxied :: FiniteBits a => proxy a -> Int
- dataTypeOfProxied :: Data a => proxy a -> DataType
- typeOfProxied :: Typeable a => proxy a -> TypeRep
- sizeOfProxied :: Storable a => proxy a -> Int
- alignmentProxied :: Storable a => proxy a -> Int
- datatypeNameProxied :: Datatype d => proxy ((t :: * -> (* -> *) -> * -> *) d f a) -> [Char]
- moduleNameProxied :: Datatype d => proxy ((t :: * -> (* -> *) -> * -> *) d f a) -> [Char]
- isNewtypeProxied :: Datatype d => proxy ((t :: * -> (* -> *) -> * -> *) d f a) -> Bool
- conNameProxied :: Constructor c => proxy ((t :: * -> (* -> *) -> * -> *) c f a) -> [Char]
- conFixityProxied :: Constructor c => proxy ((t :: * -> (* -> *) -> * -> *) c f a) -> Fixity
- conIsRecordProxied :: Constructor c => proxy ((t :: * -> (* -> *) -> * -> *) c f a) -> Bool
- selNameProxied :: Selector s => proxy ((t :: * -> (* -> *) -> * -> *) s f a) -> [Char]
- floatRadixProxied :: RealFloat a => proxy a -> Integer
- floatDigitsProxied :: RealFloat a => proxy a -> Int
- floatRangeProxied :: RealFloat a => proxy a -> (Int, Int)
- parseFormatProxied :: PrintfArg a => proxy a -> ModifierParser
proxied and unproxied
proxied :: (a -> b) -> proxy a -> b Source
Converts a constant function to one that takes a proxy argument.
Since: 0.1
unproxied :: (Proxy a -> b) -> a -> b Source
Converts a constant function that takes a Proxy argument to one that
doesn't require a proxy argument. (I'm not sure why you'd want this,
but it's here for symmetry.)
Since: 0.1
module Data.Proxy
Proxified functions
Data.Bits
bitSizeProxied :: Bits a => proxy a -> Int Source
bitSizeProxied=proxiedbitSize
Since: 0.1
isSignedProxied :: Bits a => proxy a -> Bool Source
isSignedProxied=proxiedisSigned
Since: 0.1
bitSizeMaybeProxied :: Bits a => proxy a -> Maybe Int Source
bitSizeMaybeProxied=proxiedbitSizeMaybe
This function is only available with base-4.7 or later.
Since: 0.1
finiteBitSizeProxied :: FiniteBits a => proxy a -> Int Source
finiteBitSizeProxied=proxiedfiniteBitSize
This function is only available with base-4.7 or later.
Since: 0.1
Data.Data
dataTypeOfProxied :: Data a => proxy a -> DataType Source
dataTypeOfProxied=proxieddataTypeOf
Since: 0.1
Data.Typeable
typeOfProxied :: Typeable a => proxy a -> TypeRep Source
Foreign.Storable
sizeOfProxied :: Storable a => proxy a -> Int Source
sizeOfProxied=proxiedsizeOf
Since: 0.1
alignmentProxied :: Storable a => proxy a -> Int Source
alignmentProxied=proxiedalignment
Since: 0.1
GHC.Generics
datatypeNameProxied :: Datatype d => proxy ((t :: * -> (* -> *) -> * -> *) d f a) -> [Char] Source
datatypeNameProxied=proxieddatatypeName
Since: 0.1
moduleNameProxied :: Datatype d => proxy ((t :: * -> (* -> *) -> * -> *) d f a) -> [Char] Source
moduleNameProxied=proxiedmoduleName
Since: 0.1
isNewtypeProxied :: Datatype d => proxy ((t :: * -> (* -> *) -> * -> *) d f a) -> Bool Source
isNewtypeProxied=proxiedisNewtype
This function is only available with base-4.7 or later.
Since: 0.1
conNameProxied :: Constructor c => proxy ((t :: * -> (* -> *) -> * -> *) c f a) -> [Char] Source
conNameProxied=proxiedconName
Since: 0.1
conFixityProxied :: Constructor c => proxy ((t :: * -> (* -> *) -> * -> *) c f a) -> Fixity Source
conFixityProxied=proxiedconFixity
Since: 0.1
conIsRecordProxied :: Constructor c => proxy ((t :: * -> (* -> *) -> * -> *) c f a) -> Bool Source
conIsRecordProxied=proxiedconIsRecord
Since: 0.1
selNameProxied :: Selector s => proxy ((t :: * -> (* -> *) -> * -> *) s f a) -> [Char] Source
selNameProxied=proxiedselName
Since: 0.1
Prelude
floatRadixProxied :: RealFloat a => proxy a -> Integer Source
floatRadixProxied=proxiedfloatRadix
Since: 0.1
floatDigitsProxied :: RealFloat a => proxy a -> Int Source
floatDigitsProxied=proxiedfloatDigits
Since: 0.1
floatRangeProxied :: RealFloat a => proxy a -> (Int, Int) Source
floatRangeProxied=proxiedfloatRange
Since: 0.1
Text.Printf
parseFormatProxied :: PrintfArg a => proxy a -> ModifierParser Source
parseFormatProxied=proxiedparseFormat
This function is only available with base-4.7 or later.
Since: 0.1