[project @ 1996-04-05 08:26:04 by partain]
[ghc-hetmet.git] / ghc / compiler / hsSyn / HsMatches.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1996
3 %
4 \section[HsMatches]{Abstract syntax: matches and guarded right-hand-sides}
5
6 The @Match@, @GRHSsAndBinds@ and @GRHS@ datatypes.
7
8 \begin{code}
9 #include "HsVersions.h"
10
11 module HsMatches where
12
13 import Ubiq{-uitous-}
14
15 import HsLoop           ( HsExpr, nullBinds, HsBinds )
16 import Outputable       ( ifPprShowAll )
17 import PprType
18 import Pretty
19 import SrcLoc           ( SrcLoc{-instances-} )
20 import Util             ( panic )
21 \end{code}
22
23 %************************************************************************
24 %*                                                                      *
25 \subsection{@Match@, @GRHSsAndBinds@, and @GRHS@ datatypes}
26 %*                                                                      *
27 %************************************************************************
28
29 @Match@es are sets of pattern bindings and right hand sides for
30 functions, patterns or case branches. For example, if a function @g@
31 is defined as:
32 \begin{verbatim}
33 g (x,y) = y
34 g ((x:ys),y) = y+1,
35 \end{verbatim}
36 then \tr{g} has two @Match@es: @(x,y) = y@ and @((x:ys),y) = y+1@.
37
38 It is always the case that each element of an @[Match]@ list has the
39 same number of @PatMatch@s inside it.  This corresponds to saying that
40 a function defined by pattern matching must have the same number of
41 patterns in each equation.
42
43 \begin{code}
44 data Match tyvar uvar id pat
45   = PatMatch        pat
46                     (Match tyvar uvar id pat)
47   | GRHSMatch       (GRHSsAndBinds tyvar uvar id pat)
48 \end{code}
49
50 Sets of guarded right hand sides (GRHSs). In:
51 \begin{verbatim}
52 f (x,y) | x==True = y
53         | otherwise = y*2
54 \end{verbatim}
55 a guarded right hand side is either
56 @(x==True = y)@, or @(otherwise = y*2)@.
57
58 For each match, there may be several guarded right hand
59 sides, as the definition of @f@ shows.
60
61 \begin{code}
62 data GRHSsAndBinds tyvar uvar id pat
63   = GRHSsAndBindsIn     [GRHS tyvar uvar id pat]            -- at least one GRHS
64                         (HsBinds tyvar uvar id pat)
65
66   | GRHSsAndBindsOut    [GRHS tyvar uvar id pat]            -- at least one GRHS
67                         (HsBinds tyvar uvar id pat)
68                         (GenType tyvar uvar)
69
70 data GRHS tyvar uvar id pat
71   = GRHS            (HsExpr tyvar uvar id pat)  -- guard(ed)...
72                     (HsExpr tyvar uvar id pat)  -- ... right-hand side
73                     SrcLoc
74
75   | OtherwiseGRHS   (HsExpr tyvar uvar id pat)  -- guard-free
76                     SrcLoc
77 \end{code}
78
79 %************************************************************************
80 %*                                                                      *
81 \subsection{Printing}
82 %*                                                                      *
83 %************************************************************************
84
85 We know the list must have at least one @Match@ in it.
86 \begin{code}
87 pprMatches :: (NamedThing id, Outputable id, Outputable pat,
88                Eq tyvar, Outputable tyvar, Eq uvar, Outputable uvar) =>
89                 PprStyle -> (Bool, Pretty) -> [Match tyvar uvar id pat] -> Pretty
90
91 pprMatches sty print_info@(is_case, name) [match]
92   = if is_case then
93         pprMatch sty is_case match
94     else
95         ppHang name 4 (pprMatch sty is_case match)
96
97 pprMatches sty print_info (match1 : rest)
98  = ppAbove (pprMatches sty print_info [match1])
99            (pprMatches sty print_info rest)
100
101 ---------------------------------------------
102 pprMatch :: (NamedThing id, Outputable id, Outputable pat,
103                Eq tyvar, Outputable tyvar, Eq uvar, Outputable uvar) =>
104         PprStyle -> Bool -> Match tyvar uvar id pat -> Pretty
105
106 pprMatch sty is_case first_match
107  = ppHang (ppSep (map (ppr sty) row_of_pats))
108         8 grhss_etc_stuff
109  where
110     (row_of_pats, grhss_etc_stuff) = ppr_match sty is_case first_match
111
112     ppr_match sty is_case (PatMatch pat match)
113      = (pat:pats, grhss_stuff)
114      where
115         (pats, grhss_stuff) = ppr_match sty is_case match
116
117     ppr_match sty is_case (GRHSMatch grhss_n_binds)
118      = ([], pprGRHSsAndBinds sty is_case grhss_n_binds)
119
120 ----------------------------------------------------------
121
122 pprGRHSsAndBinds sty is_case (GRHSsAndBindsIn grhss binds)
123  = ppAbove (ppAboves (map (pprGRHS sty is_case) grhss))
124            (if (nullBinds binds)
125             then ppNil
126             else ppAboves [ ppStr "where", ppNest 4 (ppr sty binds) ])
127
128 pprGRHSsAndBinds sty is_case (GRHSsAndBindsOut grhss binds ty)
129  = ppAbove (ppAboves (map (pprGRHS sty is_case) grhss))
130            (if (nullBinds binds)
131             then ppNil
132             else ppAboves [ ifPprShowAll sty
133                                 (ppCat [ppStr "{- ty:", ppr sty ty, ppStr "-}"]),
134                             ppStr "where", ppNest 4 (ppr sty binds) ])
135
136 ---------------------------------------------
137 pprGRHS :: (NamedThing id, Outputable id, Outputable pat,
138             Eq tyvar, Outputable tyvar, Eq uvar, Outputable uvar)
139         => PprStyle -> Bool -> GRHS tyvar uvar id pat -> Pretty
140
141 pprGRHS sty is_case (GRHS guard expr locn)
142  = ppHang (ppCat [ppChar '|', ppr sty guard, ppStr (if is_case then "->" else "=")])
143         4 (ppr sty expr)
144
145 pprGRHS sty is_case (OtherwiseGRHS  expr locn)
146   = ppHang (ppStr (if is_case then "->" else "="))
147          4 (ppr sty expr)
148 \end{code}