blob: 083db91291f6fd2a58b9da93dba769906a2c6f94 (
plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
|
{-# LANGUAGE NoImplicitPrelude, Trustworthy #-}
{-# LANGUAGE PolyKinds #-}
-----------------------------------------------------------------------------
-- |
-- Module : Data.Proxy
-- License : BSD-style (see the LICENSE file in the distribution)
--
-- Maintainer : libraries@haskell.org
-- Stability : experimental
-- Portability : portable
--
-- Definition of a Proxy type (poly-kinded in GHC)
--
-----------------------------------------------------------------------------
module Data.Proxy
(
Proxy(..), asProxyTypeOf
, KProxy(..)
) where
import Data.Monoid
import GHC.Base
import GHC.Show
import GHC.Read
import GHC.Enum
import GHC.Arr
-- | A concrete, poly-kinded proxy type
data Proxy t = Proxy
-- | A concrete, promotable proxy type, for use at the kind level
-- There are no instances for this because it is intended at the kind level only
data KProxy (t :: *) = KProxy
instance Eq (Proxy s) where
_ == _ = True
instance Ord (Proxy s) where
compare _ _ = EQ
instance Show (Proxy s) where
showsPrec _ _ = showString "Proxy"
instance Read (Proxy s) where
readsPrec d = readParen (d > 10) (\r -> [(Proxy, s) | ("Proxy",s) <- lex r ])
instance Enum (Proxy s) where
succ _ = error "Proxy.succ"
pred _ = error "Proxy.pred"
fromEnum _ = 0
toEnum 0 = Proxy
toEnum _ = error "Proxy.toEnum: 0 expected"
enumFrom _ = [Proxy]
enumFromThen _ _ = [Proxy]
enumFromThenTo _ _ _ = [Proxy]
enumFromTo _ _ = [Proxy]
instance Ix (Proxy s) where
range _ = [Proxy]
index _ _ = 0
inRange _ _ = True
rangeSize _ = 1
unsafeIndex _ _ = 0
unsafeRangeSize _ = 1
instance Bounded (Proxy s) where
minBound = Proxy
maxBound = Proxy
instance Functor Proxy where
fmap _ _ = Proxy
{-# INLINE fmap #-}
instance Monoid (Proxy s) where
mempty = Proxy
{-# INLINE mempty #-}
mappend _ _ = Proxy
{-# INLINE mappend #-}
mconcat _ = Proxy
{-# INLINE mconcat #-}
instance Monad Proxy where
return _ = Proxy
{-# INLINE return #-}
_ >>= _ = Proxy
{-# INLINE (>>=) #-}
-- | 'asProxyTypeOf' is a type-restricted version of 'const'.
-- It is usually used as an infix operator, and its typing forces its first
-- argument (which is usually overloaded) to have the same type as the tag
-- of the second.
asProxyTypeOf :: a -> Proxy a -> a
asProxyTypeOf = const
{-# INLINE asProxyTypeOf #-}
|