summaryrefslogtreecommitdiff
path: root/libraries/base/Data/Proxy.hs
blob: 557cc1e4dd2ac02c0ca9276b80c163a33fb2bb55 (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
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# 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)
--
-- @since 4.7.0.0
-----------------------------------------------------------------------------

module Data.Proxy
  (
        Proxy(..), asProxyTypeOf
      , KProxy(..)
  ) where

import GHC.Base
import GHC.Show
import GHC.Read
import GHC.Enum
import GHC.Arr

-- $setup
-- >>> import Data.Void
-- >>> import Prelude

-- | 'Proxy' is a type that holds no data, but has a phantom parameter of
-- arbitrary type (or even kind). Its use is to provide type information, even
-- though there is no value available of that type (or it may be too costly to
-- create one).
--
-- Historically, @'Proxy' :: 'Proxy' a@ is a safer alternative to the
-- @'undefined :: a'@ idiom.
--
-- >>> Proxy :: Proxy (Void, Int -> Int)
-- Proxy
--
-- Proxy can even hold types of higher kinds,
--
-- >>> Proxy :: Proxy Either
-- Proxy
--
-- >>> Proxy :: Proxy Functor
-- Proxy
--
-- >>> Proxy :: Proxy complicatedStructure
-- Proxy
data Proxy t = Proxy deriving ( Bounded -- ^ @since 4.7.0.0
                              , Read    -- ^ @since 4.7.0.0
                              )

-- | 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 :: Type) = KProxy

-- It's common to use (undefined :: Proxy t) and (Proxy :: Proxy t)
-- interchangeably, so all of these instances are hand-written to be
-- lazy in Proxy arguments.

-- | @since 4.7.0.0
instance Eq (Proxy s) where
  _ == _ = True

-- | @since 4.7.0.0
instance Ord (Proxy s) where
  compare _ _ = EQ

-- | @since 4.7.0.0
instance Show (Proxy s) where
  showsPrec _ _ = showString "Proxy"

-- | @since 4.7.0.0
instance Enum (Proxy s) where
    succ _               = errorWithoutStackTrace "Proxy.succ"
    pred _               = errorWithoutStackTrace "Proxy.pred"
    fromEnum _           = 0
    toEnum 0             = Proxy
    toEnum _             = errorWithoutStackTrace "Proxy.toEnum: 0 expected"
    enumFrom _           = [Proxy]
    enumFromThen _ _     = [Proxy]
    enumFromThenTo _ _ _ = [Proxy]
    enumFromTo _ _       = [Proxy]

-- | @since 4.7.0.0
instance Ix (Proxy s) where
    range _           = [Proxy]
    index _ _         = 0
    inRange _ _       = True
    rangeSize _       = 1
    unsafeIndex _ _   = 0
    unsafeRangeSize _ = 1

-- | @since 4.9.0.0
instance Semigroup (Proxy s) where
    _ <> _ = Proxy
    sconcat _ = Proxy
    stimes _ _ = Proxy

-- | @since 4.7.0.0
instance Monoid (Proxy s) where
    mempty = Proxy
    mconcat _ = Proxy

-- | @since 4.7.0.0
instance Functor Proxy where
    fmap _ _ = Proxy
    {-# INLINE fmap #-}

-- | @since 4.7.0.0
instance Applicative Proxy where
    pure _ = Proxy
    {-# INLINE pure #-}
    _ <*> _ = Proxy
    {-# INLINE (<*>) #-}

-- | @since 4.9.0.0
instance Alternative Proxy where
    empty = Proxy
    {-# INLINE empty #-}
    _ <|> _ = Proxy
    {-# INLINE (<|>) #-}

-- | @since 4.7.0.0
instance Monad Proxy where
    _ >>= _ = Proxy
    {-# INLINE (>>=) #-}

-- | @since 4.9.0.0
instance MonadPlus Proxy

-- | '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.
--
-- >>> import Data.Word
-- >>> :type asProxyTypeOf 123 (Proxy :: Proxy Word8)
-- asProxyTypeOf 123 (Proxy :: Proxy Word8) :: Word8
--
-- Note the lower-case @proxy@ in the definition. This allows any type
-- constructor with just one argument to be passed to the function, for example
-- we could also write
--
-- >>> import Data.Word
-- >>> :type asProxyTypeOf 123 (Just (undefined :: Word8))
-- asProxyTypeOf 123 (Just (undefined :: Word8)) :: Word8
asProxyTypeOf :: a -> proxy a -> a
asProxyTypeOf = const
{-# INLINE asProxyTypeOf #-}