add some {-# LANGUAGE BangPatterns #-} to mollify GHC
[ghc-hetmet.git] / utils / genprimopcode / Parser.y
1
2 {
3 {-# LANGUAGE BangPatterns #-} -- required for versions of Happy before 1.18.6
4 {-# OPTIONS -w -Wwarn #-}
5 -- The above warning supression flag is a temporary kludge.
6 -- While working on this module you are encouraged to remove it and fix
7 -- any warnings in the module. See
8 --     http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#Warnings
9 -- for details
10
11 module Parser (parse) where
12
13 import Lexer (lex_tok)
14 import ParserM (Token(..), ParserM, run_parser, get_pos, show_pos,
15                 happyError)
16 import Syntax
17 }
18
19 %name      parsex
20 %expect    0
21 %tokentype { Token }
22 %monad     { ParserM }
23 %lexer     { lex_tok } { TEOF }
24
25 %token
26     '->'            { TArrow }
27     '='             { TEquals }
28     ','             { TComma }
29     '('             { TOpenParen }
30     ')'             { TCloseParen }
31     '(#'            { TOpenParenHash }
32     '#)'            { THashCloseParen }
33     '{'             { TOpenBrace }
34     '}'             { TCloseBrace }
35     section         { TSection }
36     primop          { TPrimop }
37     pseudoop        { TPseudoop }
38     primtype        { TPrimtype }
39     with            { TWith }
40     defaults        { TDefaults }
41     true            { TTrue }
42     false           { TFalse }
43     dyadic          { TDyadic }
44     monadic         { TMonadic }
45     compare         { TCompare }
46     genprimop       { TGenPrimOp }
47     thats_all_folks { TThatsAllFolks }
48     lowerName       { TLowerName $$ }
49     upperName       { TUpperName $$ }
50     string          { TString $$ }
51     noBraces        { TNoBraces $$ }
52
53 %%
54
55 info :: { Info }
56 info : pDefaults pEntries thats_all_folks { Info $1 $2 }
57
58 pDefaults :: { [Option] }
59 pDefaults : defaults pOptions { $2 }
60
61 pOptions :: { [Option] }
62 pOptions : pOption pOptions { $1 : $2 }
63          | {- empty -}      { [] }
64
65 pOption :: { Option }
66 pOption : lowerName '=' false               { OptionFalse  $1 }
67         | lowerName '=' true                { OptionTrue   $1 }
68         | lowerName '=' pStuffBetweenBraces { OptionString $1 $3 }
69
70 pEntries :: { [Entry] }
71 pEntries : pEntry pEntries { $1 : $2 }
72          | {- empty -}   { [] }
73
74 pEntry :: { Entry }
75 pEntry : pPrimOpSpec   { $1 }
76        | pPrimTypeSpec { $1 }
77        | pPseudoOpSpec { $1 }
78        | pSection      { $1 }
79
80 pPrimOpSpec :: { Entry }
81 pPrimOpSpec : primop upperName string pCategory pType
82               pDesc pWithOptions
83               { PrimOpSpec {
84                     cons = $2,
85                     name = $3,
86                     cat = $4,
87                     ty = $5,
88                     desc = $6,
89                     opts = $7
90                 }
91               }
92
93 pPrimTypeSpec :: { Entry }
94 pPrimTypeSpec : primtype pType pDesc pWithOptions
95                 { PrimTypeSpec { ty = $2, desc = $3, opts = $4 } }
96
97 pPseudoOpSpec :: { Entry }
98 pPseudoOpSpec : pseudoop string pType pDesc pWithOptions
99                 { PseudoOpSpec { name = $2, ty = $3, desc = $4, opts = $5 } }
100
101 pSection :: { Entry }
102 pSection : section string pDesc { Section { title = $2, desc = $3 } }
103
104 pWithOptions :: { [Option] }
105 pWithOptions : with pOptions { $2 }
106              | {- empty -}   { [] }
107
108 pCategory :: { Category }
109 pCategory : dyadic { Dyadic }
110           | monadic { Monadic }
111           | compare { Compare }
112           | genprimop { GenPrimOp }
113
114 pDesc :: { String }
115 pDesc : pStuffBetweenBraces { $1 }
116       | {- empty -}         { "" }
117
118 pStuffBetweenBraces :: { String }
119 pStuffBetweenBraces : '{' pInsides '}' { $2 }
120
121 pInsides :: { String }
122 pInsides : pInside pInsides { $1 ++ $2 }
123          | {- empty -}      { "" }
124
125 pInside :: { String }
126 pInside : '{' pInsides '}' { "{" ++ $2 ++ "}" }
127         | noBraces         { $1 }
128
129 pType :: { Ty }
130 pType : paT '->' pType { TyF $1 $3 }
131       | paT            { $1 }
132
133 -- Atomic types
134 paT :: { Ty }
135 paT : pTycon ppTs     { TyApp $1 $2 }
136     | pUnboxedTupleTy { $1 }
137     | '(' pType ')'   { $2 }
138     | lowerName       { TyVar $1 }
139
140 pUnboxedTupleTy :: { Ty }
141 pUnboxedTupleTy : '(#' pCommaTypes '#)' { TyUTup $2 }
142
143 pCommaTypes :: { [Ty] }
144 pCommaTypes : pType ',' pCommaTypes { $1 : $3 }
145             | pType                 { [$1] }
146
147 ppTs :: { [Ty] }
148 ppTs : ppT ppTs    { $1 : $2 }
149      | {- empty -} { [] }
150
151 -- Primitive types
152 ppT :: { Ty }
153 ppT : lowerName { TyVar $1 }
154     | pTycon    { TyApp $1 [] }
155
156 pTycon :: { String }
157 pTycon : upperName { $1 }
158        | '(' ')'   { "()" }
159
160 {
161 parse :: String -> Either String Info
162 parse = run_parser parsex
163 }
164