{-# LANGUAGE CPP #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE ScopedTypeVariables #-}
#if __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE Trustworthy #-}
#endif
#if __GLASGOW_HASKELL__ >= 706
{-# LANGUAGE PolyKinds #-}
#endif
#if __GLASGOW_HASKELL__ >= 800 && __GLASGOW_HASKELL__ < 806
{-# LANGUAGE TypeInType #-}
#endif
{-# OPTIONS_GHC -fno-warn-deprecations #-}
module Data.Proxied (
proxied
#if MIN_VERSION_base(4,7,0)
, proxyHashed
#endif
, unproxied
, module Data.Proxy
, bitSizeProxied
, isSignedProxied
#if MIN_VERSION_base(4,7,0)
, bitSizeMaybeProxied
, finiteBitSizeProxied
#endif
, dataTypeOfProxied
, typeOfProxied
, sizeOfProxied
, alignmentProxied
, datatypeNameProxied
, moduleNameProxied
#if MIN_VERSION_base(4,7,0)
, isNewtypeProxied
#endif
#if MIN_VERSION_base(4,9,0)
, packageNameProxied
#endif
, conNameProxied
, conFixityProxied
, conIsRecordProxied
, selNameProxied
#if MIN_VERSION_base(4,9,0)
, selSourceUnpackednessProxied
, selSourceStrictnessProxied
, selDecidedStrictnessProxied
#endif
, floatRadixProxied
, floatDigitsProxied
, floatRangeProxied
#if MIN_VERSION_base(4,7,0)
, parseFormatProxied
#endif
) where
import Data.Bits (Bits(..))
import Data.Data hiding (Fixity)
#if MIN_VERSION_base(4,9,0)
import Data.Kind (Type)
#endif
import Data.Proxy
import Foreign.Storable (Storable(..))
#if MIN_VERSION_base(4,6,0)
import GHC.Generics
#else
import Generics.Deriving.Base
import Generics.Deriving.Instances ()
#endif
#if MIN_VERSION_base(4,7,0)
import Data.Bits (FiniteBits(..))
import GHC.Exts (Proxy#)
import Text.Printf (PrintfArg(..), ModifierParser)
#endif
proxied :: forall proxy a b. (a -> b) -> proxy a -> b
proxied :: forall (proxy :: * -> *) a b. (a -> b) -> proxy a -> b
proxied a -> b
f proxy a
_ = a -> b
f a
forall a. HasCallStack => a
undefined
#if MIN_VERSION_base(4,7,0)
proxyHashed :: forall a b. (a -> b) -> Proxy# a -> b
proxyHashed :: forall a b. (a -> b) -> Proxy# a -> b
proxyHashed a -> b
f Proxy# a
_ = a -> b
f a
forall a. HasCallStack => a
undefined
#endif
unproxied :: forall a b. (Proxy a -> b) -> a -> b
unproxied :: forall a b. (Proxy a -> b) -> a -> b
unproxied Proxy a -> b
f a
_ = Proxy a -> b
f Proxy a
forall {k} (t :: k). Proxy t
Proxy
bitSizeProxied :: forall proxy a. Bits a => proxy a -> Int
bitSizeProxied :: forall (proxy :: * -> *) a. Bits a => proxy a -> Int
bitSizeProxied = (a -> Int) -> proxy a -> Int
forall (proxy :: * -> *) a b. (a -> b) -> proxy a -> b
proxied a -> Int
forall a. Bits a => a -> Int
bitSize
isSignedProxied :: forall proxy a. Bits a => proxy a -> Bool
isSignedProxied :: forall (proxy :: * -> *) a. Bits a => proxy a -> Bool
isSignedProxied = (a -> Bool) -> proxy a -> Bool
forall (proxy :: * -> *) a b. (a -> b) -> proxy a -> b
proxied a -> Bool
forall a. Bits a => a -> Bool
isSigned
#if MIN_VERSION_base(4,7,0)
bitSizeMaybeProxied :: forall proxy a. Bits a => proxy a -> Maybe Int
bitSizeMaybeProxied :: forall (proxy :: * -> *) a. Bits a => proxy a -> Maybe Int
bitSizeMaybeProxied = (a -> Maybe Int) -> proxy a -> Maybe Int
forall (proxy :: * -> *) a b. (a -> b) -> proxy a -> b
proxied a -> Maybe Int
forall a. Bits a => a -> Maybe Int
bitSizeMaybe
finiteBitSizeProxied :: forall proxy a. FiniteBits a => proxy a -> Int
finiteBitSizeProxied :: forall (proxy :: * -> *) a. FiniteBits a => proxy a -> Int
finiteBitSizeProxied = (a -> Int) -> proxy a -> Int
forall (proxy :: * -> *) a b. (a -> b) -> proxy a -> b
proxied a -> Int
forall b. FiniteBits b => b -> Int
finiteBitSize
#endif
dataTypeOfProxied :: forall proxy a. Data a => proxy a -> DataType
dataTypeOfProxied :: forall (proxy :: * -> *) a. Data a => proxy a -> DataType
dataTypeOfProxied = (a -> DataType) -> proxy a -> DataType
forall (proxy :: * -> *) a b. (a -> b) -> proxy a -> b
proxied a -> DataType
forall a. Data a => a -> DataType
dataTypeOf
typeOfProxied :: forall
#if MIN_VERSION_base(4,9,0)
k
#endif
proxy
#if MIN_VERSION_base(4,7,0)
(a :: k)
#else
a
#endif
. Typeable a => proxy a -> TypeRep
#if MIN_VERSION_base(4,7,0)
typeOfProxied :: forall k (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
typeOfProxied = proxy a -> TypeRep
forall k (proxy :: k -> *) (a :: k).
Typeable a =>
proxy a -> TypeRep
typeRep
#else
typeOfProxied = proxied typeOf
#endif
sizeOfProxied :: forall proxy a. Storable a => proxy a -> Int
sizeOfProxied :: forall (proxy :: * -> *) a. Storable a => proxy a -> Int
sizeOfProxied = (a -> Int) -> proxy a -> Int
forall (proxy :: * -> *) a b. (a -> b) -> proxy a -> b
proxied a -> Int
forall a. Storable a => a -> Int
sizeOf
alignmentProxied :: forall proxy a. Storable a => proxy a -> Int
alignmentProxied :: forall (proxy :: * -> *) a. Storable a => proxy a -> Int
alignmentProxied = (a -> Int) -> proxy a -> Int
forall (proxy :: * -> *) a b. (a -> b) -> proxy a -> b
proxied a -> Int
forall a. Storable a => a -> Int
alignment
#define GENERIC_FORALL(t,letter) forall K_KINDS proxy T_TYPE(t) letter f a
#if MIN_VERSION_base(4,9,0)
# define K_KINDS k1 k2
#else
# define K_KINDS
#endif
#if MIN_VERSION_base(4,10,0)
# define T_TYPE(t) (t :: k1 -> (k2 -> Type) -> k2 -> Type)
#elif MIN_VERSION_base(4,9,0)
# define T_TYPE(t) (t :: k1 -> (Type -> Type) -> k2 -> Type)
#else
# define T_TYPE(t) (t :: * -> (* -> *) -> * -> *)
#endif
datatypeNameProxied :: GENERIC_FORALL(t,d). Datatype d
=> proxy (T_TYPE(t) d f a)
-> [Char]
datatypeNameProxied :: forall k1 k2 (proxy :: * -> *) (t :: k1 -> (k2 -> *) -> k2 -> *)
(d :: k1) (f :: k2 -> *) (a :: k2).
Datatype d =>
proxy (t d f a) -> [Char]
datatypeNameProxied = (t d f a -> [Char]) -> proxy (t d f a) -> [Char]
forall (proxy :: * -> *) a b. (a -> b) -> proxy a -> b
proxied t d f a -> [Char]
forall {k} (d :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
(f :: k1 -> *) (a :: k1).
Datatype d =>
t d f a -> [Char]
forall k1 (t :: k1 -> (k1 -> *) -> k1 -> *) (f :: k1 -> *)
(a :: k1).
t d f a -> [Char]
datatypeName
moduleNameProxied :: GENERIC_FORALL(t,d). Datatype d
=> proxy (T_TYPE(t) d f a)
-> [Char]
moduleNameProxied :: forall k1 k2 (proxy :: * -> *) (t :: k1 -> (k2 -> *) -> k2 -> *)
(d :: k1) (f :: k2 -> *) (a :: k2).
Datatype d =>
proxy (t d f a) -> [Char]
moduleNameProxied = (t d f a -> [Char]) -> proxy (t d f a) -> [Char]
forall (proxy :: * -> *) a b. (a -> b) -> proxy a -> b
proxied t d f a -> [Char]
forall {k} (d :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
(f :: k1 -> *) (a :: k1).
Datatype d =>
t d f a -> [Char]
forall k1 (t :: k1 -> (k1 -> *) -> k1 -> *) (f :: k1 -> *)
(a :: k1).
t d f a -> [Char]
moduleName
#if MIN_VERSION_base(4,7,0)
isNewtypeProxied :: GENERIC_FORALL(t,d). Datatype d
=> proxy (T_TYPE(t) d f a)
-> Bool
isNewtypeProxied :: forall k1 k2 (proxy :: * -> *) (t :: k1 -> (k2 -> *) -> k2 -> *)
(d :: k1) (f :: k2 -> *) (a :: k2).
Datatype d =>
proxy (t d f a) -> Bool
isNewtypeProxied = (t d f a -> Bool) -> proxy (t d f a) -> Bool
forall (proxy :: * -> *) a b. (a -> b) -> proxy a -> b
proxied t d f a -> Bool
forall {k} (d :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
(f :: k1 -> *) (a :: k1).
Datatype d =>
t d f a -> Bool
forall k1 (t :: k1 -> (k1 -> *) -> k1 -> *) (f :: k1 -> *)
(a :: k1).
t d f a -> Bool
isNewtype
#endif
#if MIN_VERSION_base(4,9,0)
packageNameProxied :: GENERIC_FORALL(t,d). Datatype d
=> proxy (T_TYPE(t) d f a)
-> [Char]
packageNameProxied :: forall k1 k2 (proxy :: * -> *) (t :: k1 -> (k2 -> *) -> k2 -> *)
(d :: k1) (f :: k2 -> *) (a :: k2).
Datatype d =>
proxy (t d f a) -> [Char]
packageNameProxied = (t d f a -> [Char]) -> proxy (t d f a) -> [Char]
forall (proxy :: * -> *) a b. (a -> b) -> proxy a -> b
proxied t d f a -> [Char]
forall {k} (d :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
(f :: k1 -> *) (a :: k1).
Datatype d =>
t d f a -> [Char]
forall k1 (t :: k1 -> (k1 -> *) -> k1 -> *) (f :: k1 -> *)
(a :: k1).
t d f a -> [Char]
packageName
#endif
conNameProxied :: GENERIC_FORALL(t,c). Constructor c
=> proxy (T_TYPE(t) c f a)
-> [Char]
conNameProxied :: forall k1 k2 (proxy :: * -> *) (t :: k1 -> (k2 -> *) -> k2 -> *)
(c :: k1) (f :: k2 -> *) (a :: k2).
Constructor c =>
proxy (t c f a) -> [Char]
conNameProxied = (t c f a -> [Char]) -> proxy (t c f a) -> [Char]
forall (proxy :: * -> *) a b. (a -> b) -> proxy a -> b
proxied t c f a -> [Char]
forall {k} (c :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
(f :: k1 -> *) (a :: k1).
Constructor c =>
t c f a -> [Char]
forall k1 (t :: k1 -> (k1 -> *) -> k1 -> *) (f :: k1 -> *)
(a :: k1).
t c f a -> [Char]
conName
conFixityProxied :: GENERIC_FORALL(t,c). Constructor c
=> proxy (T_TYPE(t) c f a)
-> Fixity
conFixityProxied :: forall k1 k2 (proxy :: * -> *) (t :: k1 -> (k2 -> *) -> k2 -> *)
(c :: k1) (f :: k2 -> *) (a :: k2).
Constructor c =>
proxy (t c f a) -> Fixity
conFixityProxied = (t c f a -> Fixity) -> proxy (t c f a) -> Fixity
forall (proxy :: * -> *) a b. (a -> b) -> proxy a -> b
proxied t c f a -> Fixity
forall {k} (c :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
(f :: k1 -> *) (a :: k1).
Constructor c =>
t c f a -> Fixity
forall k1 (t :: k1 -> (k1 -> *) -> k1 -> *) (f :: k1 -> *)
(a :: k1).
t c f a -> Fixity
conFixity
conIsRecordProxied :: GENERIC_FORALL(t,c). Constructor c
=> proxy (T_TYPE(t) c f a)
-> Bool
conIsRecordProxied :: forall k1 k2 (proxy :: * -> *) (t :: k1 -> (k2 -> *) -> k2 -> *)
(c :: k1) (f :: k2 -> *) (a :: k2).
Constructor c =>
proxy (t c f a) -> Bool
conIsRecordProxied = (t c f a -> Bool) -> proxy (t c f a) -> Bool
forall (proxy :: * -> *) a b. (a -> b) -> proxy a -> b
proxied t c f a -> Bool
forall {k} (c :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
(f :: k1 -> *) (a :: k1).
Constructor c =>
t c f a -> Bool
forall k1 (t :: k1 -> (k1 -> *) -> k1 -> *) (f :: k1 -> *)
(a :: k1).
t c f a -> Bool
conIsRecord
selNameProxied :: GENERIC_FORALL(t,s). Selector s
=> proxy (T_TYPE(t) s f a)
-> [Char]
selNameProxied :: forall k1 k2 (proxy :: * -> *) (t :: k1 -> (k2 -> *) -> k2 -> *)
(s :: k1) (f :: k2 -> *) (a :: k2).
Selector s =>
proxy (t s f a) -> [Char]
selNameProxied = (t s f a -> [Char]) -> proxy (t s f a) -> [Char]
forall (proxy :: * -> *) a b. (a -> b) -> proxy a -> b
proxied t s f a -> [Char]
forall {k} (s :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
(f :: k1 -> *) (a :: k1).
Selector s =>
t s f a -> [Char]
forall k1 (t :: k1 -> (k1 -> *) -> k1 -> *) (f :: k1 -> *)
(a :: k1).
t s f a -> [Char]
selName
#if MIN_VERSION_base(4,9,0)
selSourceUnpackednessProxied :: GENERIC_FORALL(t,s). Selector s
=> proxy (T_TYPE(t) s f a)
-> SourceUnpackedness
selSourceUnpackednessProxied :: forall k1 k2 (proxy :: * -> *) (t :: k1 -> (k2 -> *) -> k2 -> *)
(s :: k1) (f :: k2 -> *) (a :: k2).
Selector s =>
proxy (t s f a) -> SourceUnpackedness
selSourceUnpackednessProxied = (t s f a -> SourceUnpackedness)
-> proxy (t s f a) -> SourceUnpackedness
forall (proxy :: * -> *) a b. (a -> b) -> proxy a -> b
proxied t s f a -> SourceUnpackedness
forall {k} (s :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
(f :: k1 -> *) (a :: k1).
Selector s =>
t s f a -> SourceUnpackedness
forall k1 (t :: k1 -> (k1 -> *) -> k1 -> *) (f :: k1 -> *)
(a :: k1).
t s f a -> SourceUnpackedness
selSourceUnpackedness
selSourceStrictnessProxied :: GENERIC_FORALL(t,s). Selector s
=> proxy (T_TYPE(t) s f a)
-> SourceStrictness
selSourceStrictnessProxied :: forall k1 k2 (proxy :: * -> *) (t :: k1 -> (k2 -> *) -> k2 -> *)
(s :: k1) (f :: k2 -> *) (a :: k2).
Selector s =>
proxy (t s f a) -> SourceStrictness
selSourceStrictnessProxied = (t s f a -> SourceStrictness)
-> proxy (t s f a) -> SourceStrictness
forall (proxy :: * -> *) a b. (a -> b) -> proxy a -> b
proxied t s f a -> SourceStrictness
forall {k} (s :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
(f :: k1 -> *) (a :: k1).
Selector s =>
t s f a -> SourceStrictness
forall k1 (t :: k1 -> (k1 -> *) -> k1 -> *) (f :: k1 -> *)
(a :: k1).
t s f a -> SourceStrictness
selSourceStrictness
selDecidedStrictnessProxied :: GENERIC_FORALL(t,s). Selector s
=> proxy (T_TYPE(t) s f a)
-> DecidedStrictness
selDecidedStrictnessProxied :: forall k1 k2 (proxy :: * -> *) (t :: k1 -> (k2 -> *) -> k2 -> *)
(s :: k1) (f :: k2 -> *) (a :: k2).
Selector s =>
proxy (t s f a) -> DecidedStrictness
selDecidedStrictnessProxied = (t s f a -> DecidedStrictness)
-> proxy (t s f a) -> DecidedStrictness
forall (proxy :: * -> *) a b. (a -> b) -> proxy a -> b
proxied t s f a -> DecidedStrictness
forall {k} (s :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
(f :: k1 -> *) (a :: k1).
Selector s =>
t s f a -> DecidedStrictness
forall k1 (t :: k1 -> (k1 -> *) -> k1 -> *) (f :: k1 -> *)
(a :: k1).
t s f a -> DecidedStrictness
selDecidedStrictness
#endif
floatRadixProxied :: forall proxy a. RealFloat a => proxy a -> Integer
floatRadixProxied :: forall (proxy :: * -> *) a. RealFloat a => proxy a -> Integer
floatRadixProxied = (a -> Integer) -> proxy a -> Integer
forall (proxy :: * -> *) a b. (a -> b) -> proxy a -> b
proxied a -> Integer
forall a. RealFloat a => a -> Integer
floatRadix
floatDigitsProxied :: forall proxy a. RealFloat a => proxy a -> Int
floatDigitsProxied :: forall (proxy :: * -> *) a. RealFloat a => proxy a -> Int
floatDigitsProxied = (a -> Int) -> proxy a -> Int
forall (proxy :: * -> *) a b. (a -> b) -> proxy a -> b
proxied a -> Int
forall a. RealFloat a => a -> Int
floatDigits
floatRangeProxied :: forall proxy a. RealFloat a => proxy a -> (Int, Int)
floatRangeProxied :: forall (proxy :: * -> *) a. RealFloat a => proxy a -> (Int, Int)
floatRangeProxied = (a -> (Int, Int)) -> proxy a -> (Int, Int)
forall (proxy :: * -> *) a b. (a -> b) -> proxy a -> b
proxied a -> (Int, Int)
forall a. RealFloat a => a -> (Int, Int)
floatRange
#if MIN_VERSION_base(4,7,0)
parseFormatProxied :: forall proxy a. PrintfArg a => proxy a -> ModifierParser
parseFormatProxied :: forall (proxy :: * -> *) a.
PrintfArg a =>
proxy a -> ModifierParser
parseFormatProxied = (a -> ModifierParser) -> proxy a -> ModifierParser
forall (proxy :: * -> *) a b. (a -> b) -> proxy a -> b
proxied a -> ModifierParser
forall a. PrintfArg a => a -> ModifierParser
parseFormat
#endif