summaryrefslogtreecommitdiff
path: root/compiler/basicTypes/PatSyn.lhs
blob: 2081b5af843decc7cfed82282ec768f2f4fce32f (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
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
%
% (c) The University of Glasgow 2006
% (c) The GRASP/AQUA Project, Glasgow University, 1998
%
\section[PatSyn]{@PatSyn@: Pattern synonyms}

\begin{code}
{-# LANGUAGE CPP, DeriveDataTypeable #-}

module PatSyn (
        -- * Main data types
        PatSyn, mkPatSyn,

        -- ** Type deconstruction
        patSynName, patSynArity, patSynIsInfix,
        patSynArgs, patSynTyDetails, patSynType,
        patSynWrapper, patSynMatcher,
        patSynExTyVars, patSynSig,
        patSynInstArgTys, patSynInstResTy,
        tidyPatSynIds
    ) where

#include "HsVersions.h"

import Type
import TcType( mkSigmaTy )
import Name
import Outputable
import Unique
import Util
import BasicTypes
import FastString
import Var
import HsBinds( HsPatSynDetails(..) )

import qualified Data.Data as Data
import qualified Data.Typeable
import Data.Function
\end{code}


Note [Pattern synonym representation]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Consider the following pattern synonym declaration

        pattern P x = MkT [x] (Just 42)

where
        data T a where
              MkT :: (Show a, Ord b) => [b] -> a -> T a

so pattern P has type

        b -> T (Maybe t)

with the following typeclass constraints:

        provides: (Show (Maybe t), Ord b)
        requires: (Eq t, Num t)

In this case, the fields of MkPatSyn will be set as follows:

  psArgs       = [b]
  psArity      = 1
  psInfix      = False

  psUnivTyVars = [t]
  psExTyVars   = [b]
  psProvTheta  = (Show (Maybe t), Ord b)
  psReqTheta   = (Eq t, Num t)
  psOrigResTy  = T (Maybe t)

Note [Matchers and wrappers for pattern synonyms]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
For each pattern synonym, we generate a single matcher function which
implements the actual matching. For the above example, the matcher
will have type:

        $mP :: forall r t. (Eq t, Num t)
            => T (Maybe t)
            -> (forall b. (Show (Maybe t), Ord b) => b -> r)
            -> r
            -> r

with the following implementation:

        $mP @r @t $dEq $dNum scrut cont fail = case scrut of
            MkT @b $dShow $dOrd [x] (Just 42) -> cont @b $dShow $dOrd x
            _                                 -> fail

For *bidirectional* pattern synonyms, we also generate a single wrapper
function which implements the pattern synonym in an expression
context. For our running example, it will be:

        $WP :: forall t b. (Show (Maybe t), Ord b, Eq t, Num t)
            => b -> T (Maybe t)
        $WP x = MkT [x] (Just 42)

NB: the existential/universal and required/provided split does not
apply to the wrapper since you are only putting stuff in, not getting
stuff out.

Injectivity of bidirectional pattern synonyms is checked in
tcPatToExpr which walks the pattern and returns its corresponding
expression when available.

%************************************************************************
%*                                                                      *
\subsection{Pattern synonyms}
%*                                                                      *
%************************************************************************

\begin{code}
-- | A pattern synonym
-- See Note [Pattern synonym representation]
data PatSyn
  = MkPatSyn {
        psName        :: Name,
        psUnique      :: Unique,      -- Cached from Name

        psArgs        :: [Type],
        psArity       :: Arity,       -- == length psArgs
        psInfix       :: Bool,        -- True <=> declared infix

        psUnivTyVars  :: [TyVar],     -- Universially-quantified type variables
        psExTyVars    :: [TyVar],     -- Existentially-quantified type vars
        psProvTheta   :: ThetaType,   -- Provided dictionaries
        psReqTheta    :: ThetaType,   -- Required dictionaries
        psOrigResTy   :: Type,        -- Mentions only psUnivTyVars

        -- See Note [Matchers and wrappers for pattern synonyms]
        psMatcher     :: Id,
             -- Matcher function, of type
             --   forall r univ_tvs. req_theta
             --                   => res_ty
             --                   -> (forall ex_tvs. prov_theta -> arg_tys -> r)
             --                   -> r -> r

        psWrapper     :: Maybe Id
             -- Nothing  => uni-directional pattern synonym
             -- Just wid => bi-direcitonal
             -- Wrapper function, of type
             --  forall univ_tvs, ex_tvs. (prov_theta, req_theta)
             --                       =>  arg_tys -> res_ty
  }
  deriving Data.Typeable.Typeable
\end{code}

%************************************************************************
%*                                                                      *
\subsection{Instances}
%*                                                                      *
%************************************************************************

\begin{code}
instance Eq PatSyn where
    (==) = (==) `on` getUnique
    (/=) = (/=) `on` getUnique

instance Ord PatSyn where
    (<=) = (<=) `on` getUnique
    (<) = (<) `on` getUnique
    (>=) = (>=) `on` getUnique
    (>) = (>) `on` getUnique
    compare = compare `on` getUnique

instance Uniquable PatSyn where
    getUnique = psUnique

instance NamedThing PatSyn where
    getName = patSynName

instance Outputable PatSyn where
    ppr = ppr . getName

instance OutputableBndr PatSyn where
    pprInfixOcc = pprInfixName . getName
    pprPrefixOcc = pprPrefixName . getName

instance Data.Data PatSyn where
    -- don't traverse?
    toConstr _   = abstractConstr "PatSyn"
    gunfold _ _  = error "gunfold"
    dataTypeOf _ = mkNoRepType "PatSyn"
\end{code}


%************************************************************************
%*                                                                      *
\subsection{Construction}
%*                                                                      *
%************************************************************************

\begin{code}
-- | Build a new pattern synonym
mkPatSyn :: Name
         -> Bool       -- ^ Is the pattern synonym declared infix?
         -> [Type]     -- ^ Original arguments
         -> [TyVar]    -- ^ Universially-quantified type variables
         -> [TyVar]    -- ^ Existentially-quantified type variables
         -> ThetaType  -- ^ Wanted dicts
         -> ThetaType  -- ^ Given dicts
         -> Type       -- ^ Original result type
         -> Id         -- ^ Name of matcher
         -> Maybe Id   -- ^ Name of wrapper
         -> PatSyn
mkPatSyn name declared_infix orig_args
         univ_tvs ex_tvs
         prov_theta req_theta
         orig_res_ty
         matcher wrapper
    = MkPatSyn {psName = name, psUnique = getUnique name,
                psUnivTyVars = univ_tvs, psExTyVars = ex_tvs,
                psProvTheta = prov_theta, psReqTheta = req_theta,
                psInfix = declared_infix,
                psArgs = orig_args,
                psArity = length orig_args,
                psOrigResTy = orig_res_ty,
                psMatcher = matcher,
                psWrapper = wrapper }
\end{code}

\begin{code}
-- | The 'Name' of the 'PatSyn', giving it a unique, rooted identification
patSynName :: PatSyn -> Name
patSynName = psName

patSynType :: PatSyn -> Type
-- The full pattern type, used only in error messages
patSynType (MkPatSyn { psUnivTyVars = univ_tvs, psReqTheta = req_theta
                     , psExTyVars   = ex_tvs,   psProvTheta = prov_theta
                     , psArgs = orig_args, psOrigResTy = orig_res_ty })
  = mkSigmaTy univ_tvs req_theta $
    mkSigmaTy ex_tvs prov_theta $
    mkFunTys orig_args orig_res_ty

-- | Should the 'PatSyn' be presented infix?
patSynIsInfix :: PatSyn -> Bool
patSynIsInfix = psInfix

-- | Arity of the pattern synonym
patSynArity :: PatSyn -> Arity
patSynArity = psArity

patSynArgs :: PatSyn -> [Type]
patSynArgs = psArgs

patSynTyDetails :: PatSyn -> HsPatSynDetails Type
patSynTyDetails (MkPatSyn { psInfix = is_infix, psArgs = arg_tys })
  | is_infix, [left,right] <- arg_tys
  = InfixPatSyn left right
  | otherwise
  = PrefixPatSyn arg_tys

patSynExTyVars :: PatSyn -> [TyVar]
patSynExTyVars = psExTyVars

patSynSig :: PatSyn -> ([TyVar], [TyVar], ThetaType, ThetaType, [Type], Type)
patSynSig (MkPatSyn { psUnivTyVars = univ_tvs, psExTyVars = ex_tvs
                    , psProvTheta = prov, psReqTheta = req
                    , psArgs = arg_tys, psOrigResTy = res_ty })
  = (univ_tvs, ex_tvs, prov, req, arg_tys, res_ty)

patSynWrapper :: PatSyn -> Maybe Id
patSynWrapper = psWrapper

patSynMatcher :: PatSyn -> Id
patSynMatcher = psMatcher

tidyPatSynIds :: (Id -> Id) -> PatSyn -> PatSyn
tidyPatSynIds tidy_fn ps@(MkPatSyn { psMatcher = match_id, psWrapper = mb_wrap_id })
  = ps { psMatcher = tidy_fn match_id, psWrapper = fmap tidy_fn mb_wrap_id }

patSynInstArgTys :: PatSyn -> [Type] -> [Type]
-- Return the types of the argument patterns
-- e.g.  data D a = forall b. MkD a b (b->a)
--       pattern P f x y = MkD (x,True) y f
--          D :: forall a. forall b. a -> b -> (b->a) -> D a
--          P :: forall c. forall b. (b->(c,Bool)) -> c -> b -> P c
--   patSynInstArgTys P [Int,bb] = [bb->(Int,Bool), Int, bb]
-- NB: the inst_tys should be both universal and existential
patSynInstArgTys (MkPatSyn { psName = name, psUnivTyVars = univ_tvs
                           , psExTyVars = ex_tvs, psArgs = arg_tys })
                 inst_tys
  = ASSERT2( length tyvars == length inst_tys
          , ptext (sLit "patSynInstArgTys") <+> ppr name $$ ppr tyvars $$ ppr inst_tys )
    map (substTyWith tyvars inst_tys) arg_tys
  where
    tyvars = univ_tvs ++ ex_tvs

patSynInstResTy :: PatSyn -> [Type] -> Type
-- Return the type of whole pattern
-- E.g.  pattern P x y = Just (x,x,y)
--         P :: a -> b -> Just (a,a,b)
--         (patSynInstResTy P [Int,Bool] = Maybe (Int,Int,Bool)
-- NB: unlikepatSynInstArgTys, the inst_tys should be just the *universal* tyvars
patSynInstResTy (MkPatSyn { psName = name, psUnivTyVars = univ_tvs
                          , psOrigResTy = res_ty })
                inst_tys
  = ASSERT2( length univ_tvs == length inst_tys
           , ptext (sLit "patSynInstResTy") <+> ppr name $$ ppr univ_tvs $$ ppr inst_tys )
    substTyWith univ_tvs inst_tys res_ty
\end{code}