proxied-0.3.2: Make functions consume Proxy instead of undefined
Copyright(C) 2016-2017 Ryan Scott
LicenseBSD-style (see the file LICENSE)
MaintainerRyan Scott
StabilityProvisional
PortabilityGHC
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Proxied

Description

Convert undefined-consuming functions to Proxy-consuming ones with proxied.

Since: 0.1

Synopsis

proxied and unproxied

proxied :: forall proxy a b. (a -> b) -> proxy a -> b Source #

Converts a constant function to one that takes a proxy argument.

Since: 0.1

proxyHashed :: forall a b. (a -> b) -> Proxy# a -> b Source #

Converts a constant function to one that takes a Proxy# argument. This function is only available with base-4.7 or later.

Since: 0.2

unproxied :: forall a b. (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 :: forall proxy a. Bits a => proxy a -> Int Source #

isSignedProxied :: forall proxy a. Bits a => proxy a -> Bool Source #

bitSizeMaybeProxied :: forall proxy a. Bits a => proxy a -> Maybe Int Source #

bitSizeMaybeProxied = proxied bitSizeMaybe

This function is only available with base-4.7 or later.

Since: 0.1

finiteBitSizeProxied :: forall proxy a. FiniteBits a => proxy a -> Int Source #

finiteBitSizeProxied = proxied finiteBitSize

This function is only available with base-4.7 or later.

Since: 0.1

Data.Data

dataTypeOfProxied :: forall proxy a. Data a => proxy a -> DataType Source #

Data.Typeable

typeOfProxied :: forall k proxy (a :: k). Typeable a => proxy a -> TypeRep Source #

typeOfProxied = proxied typeOf

On base-4.7 and later, this is identical to typeRep.

Since: 0.1

Foreign.Storable

sizeOfProxied :: forall proxy a. Storable a => proxy a -> Int Source #

alignmentProxied :: forall proxy a. Storable a => proxy a -> Int Source #

GHC.Generics

datatypeNameProxied :: forall k1 k2 proxy (t :: k1 -> (k2 -> Type) -> k2 -> Type) d f a. Datatype d => proxy ((t :: k1 -> (k2 -> Type) -> k2 -> Type) d f a) -> [Char] Source #

moduleNameProxied :: forall k1 k2 proxy (t :: k1 -> (k2 -> Type) -> k2 -> Type) d f a. Datatype d => proxy ((t :: k1 -> (k2 -> Type) -> k2 -> Type) d f a) -> [Char] Source #

isNewtypeProxied :: forall k1 k2 proxy (t :: k1 -> (k2 -> Type) -> k2 -> Type) d f a. Datatype d => proxy ((t :: k1 -> (k2 -> Type) -> k2 -> Type) d f a) -> Bool Source #

isNewtypeProxied = proxied isNewtype

This function is only available with base-4.7 or later.

Since: 0.1

packageNameProxied :: forall k1 k2 proxy (t :: k1 -> (k2 -> Type) -> k2 -> Type) d f a. Datatype d => proxy ((t :: k1 -> (k2 -> Type) -> k2 -> Type) d f a) -> [Char] Source #

packageNameProxied = proxied packageName

This function is only avaiable with base-4.9 or later.

Since: 0.1

conNameProxied :: forall k1 k2 proxy (t :: k1 -> (k2 -> Type) -> k2 -> Type) c f a. Constructor c => proxy ((t :: k1 -> (k2 -> Type) -> k2 -> Type) c f a) -> [Char] Source #

conFixityProxied :: forall k1 k2 proxy (t :: k1 -> (k2 -> Type) -> k2 -> Type) c f a. Constructor c => proxy ((t :: k1 -> (k2 -> Type) -> k2 -> Type) c f a) -> Fixity Source #

conIsRecordProxied :: forall k1 k2 proxy (t :: k1 -> (k2 -> Type) -> k2 -> Type) c f a. Constructor c => proxy ((t :: k1 -> (k2 -> Type) -> k2 -> Type) c f a) -> Bool Source #

selNameProxied :: forall k1 k2 proxy (t :: k1 -> (k2 -> Type) -> k2 -> Type) s f a. Selector s => proxy ((t :: k1 -> (k2 -> Type) -> k2 -> Type) s f a) -> [Char] Source #

selSourceUnpackednessProxied :: forall k1 k2 proxy (t :: k1 -> (k2 -> Type) -> k2 -> Type) s f a. Selector s => proxy ((t :: k1 -> (k2 -> Type) -> k2 -> Type) s f a) -> SourceUnpackedness Source #

selSourceUnpackednessProxied = proxied selSourceUnpackedness

This function is only available with base-4.9 or later.

Since: 0.1

selSourceStrictnessProxied :: forall k1 k2 proxy (t :: k1 -> (k2 -> Type) -> k2 -> Type) s f a. Selector s => proxy ((t :: k1 -> (k2 -> Type) -> k2 -> Type) s f a) -> SourceStrictness Source #

selSourceStrictnessProxied = proxied selSourceStrictness

This function is only available with base-4.9 or later.

Since: 0.1

selDecidedStrictnessProxied :: forall k1 k2 proxy (t :: k1 -> (k2 -> Type) -> k2 -> Type) s f a. Selector s => proxy ((t :: k1 -> (k2 -> Type) -> k2 -> Type) s f a) -> DecidedStrictness Source #

selDecidedStrictnessProxied = proxied selDecidedStrictness

This function is only available with base-4.9 or later.

Since: 0.1

Prelude

floatRadixProxied :: forall proxy a. RealFloat a => proxy a -> Integer Source #

floatDigitsProxied :: forall proxy a. RealFloat a => proxy a -> Int Source #

floatRangeProxied :: forall proxy a. RealFloat a => proxy a -> (Int, Int) Source #

Text.Printf

parseFormatProxied :: forall proxy a. PrintfArg a => proxy a -> ModifierParser Source #

parseFormatProxied = proxied parseFormat

This function is only available with base-4.7 or later.

Since: 0.1