2 ------------------------------------------------------------------
3 -- A primop-table mangling program --
4 ------------------------------------------------------------------
13 import Data
.Maybe ( catMaybes )
14 import System
.Environment
( getArgs )
17 main
= getArgs >>= \args
->
18 if length args
/= 1 ||
head args `
notElem` known_args
19 then error ("usage: genprimopcode command < primops.txt > ...\n"
20 ++ " where command is one of\n"
21 ++ unlines (map (" "++) known_args
)
26 Left err
-> error ("parse error at " ++ (show err
))
27 Right p_o_specs
@(Info _ entries
)
28 -> seq (sanityTop p_o_specs
) (
32 -> putStr (gen_data_decl p_o_specs
)
35 -> putStr (gen_switch_from_attribs
37 "primOpHasSideEffects" p_o_specs
)
40 -> putStr (gen_switch_from_attribs
42 "primOpOutOfLine" p_o_specs
)
45 -> putStr (gen_switch_from_attribs
47 "commutableOp" p_o_specs
)
50 -> putStr (gen_switch_from_attribs
52 "primOpCodeSize" p_o_specs
)
55 -> putStr (gen_switch_from_attribs
57 "primOpCanFail" p_o_specs
)
60 -> putStr (gen_switch_from_attribs
62 "primOpStrictness" p_o_specs
)
65 -> putStr (gen_switch_from_attribs
67 "primOpFixity" p_o_specs
)
69 "--primop-primop-info"
70 -> putStr (gen_primop_info p_o_specs
)
73 -> putStr (gen_primop_tag p_o_specs
)
76 -> putStr (gen_primop_list p_o_specs
)
78 "--make-haskell-wrappers"
79 -> putStr (gen_wrappers p_o_specs
)
81 "--make-haskell-source"
82 -> putStr (gen_hs_source p_o_specs
)
84 "--make-ext-core-source"
85 -> putStr (gen_ext_core_source entries
)
88 -> putStr (gen_latex_doc p_o_specs
)
90 _
-> error "Should not happen, known_args out of sync?"
93 known_args
:: [String]
103 "--primop-primop-info",
106 "--make-haskell-wrappers",
107 "--make-haskell-source",
108 "--make-ext-core-source",
112 ------------------------------------------------------------------
113 -- Code generators -----------------------------------------------
114 ------------------------------------------------------------------
116 gen_hs_source
:: Info
-> String
117 gen_hs_source
(Info defaults entries
) =
119 ++ "This is a generated file (generated by genprimopcode).\n"
120 ++ "It is not code to actually be used. Its only purpose is to be\n"
121 ++ "consumed by haddock.\n"
124 ++ "-----------------------------------------------------------------------------\n"
126 ++ "-- Module : GHC.Prim\n"
128 ++ "-- Maintainer : ghc-devs@haskell.org\n"
129 ++ "-- Stability : internal\n"
130 ++ "-- Portability : non-portable (GHC extensions)\n"
132 ++ "-- GHC\'s primitive types and operations.\n"
133 ++ "-- Use GHC.Exts from the base package instead of importing this\n"
134 ++ "-- module directly.\n"
136 ++ "-----------------------------------------------------------------------------\n"
137 ++ "{-# LANGUAGE MultiParamTypeClasses #-}\n"
138 ++ "module GHC.Prim (\n"
139 ++ unlines (map (("\t" ++) . hdr
) entries
)
143 ++ unlines (map opt defaults
)
145 ++ unlines (concatMap ent entries
) ++ "\n\n\n"
146 where opt
(OptionFalse n
) = n
++ " = False"
147 opt
(OptionTrue n
) = n
++ " = True"
148 opt
(OptionString n v
) = n
++ " = { " ++ v
++ "}"
149 opt
(OptionInteger n v
) = n
++ " = " ++ show v
150 opt
(OptionFixity mf
) = "fixity" ++ " = " ++ show mf
152 hdr s
@(Section
{}) = sec s
153 hdr
(PrimOpSpec
{ name
= n
}) = wrapOp n
++ ","
154 hdr
(PseudoOpSpec
{ name
= n
}) = wrapOp n
++ ","
155 hdr
(PrimTypeSpec
{ ty
= TyApp n _
}) = wrapTy n
++ ","
156 hdr
(PrimTypeSpec
{}) = error "Illegal type spec"
157 hdr
(PrimClassSpec
{ cls
= TyApp n _
}) = wrapTy n
++ ","
158 hdr
(PrimClassSpec
{}) = error "Illegal class spec"
160 ent
(Section
{}) = []
161 ent o
@(PrimOpSpec
{}) = spec o
162 ent o
@(PrimTypeSpec
{}) = spec o
163 ent o
@(PrimClassSpec
{}) = spec o
164 ent o
@(PseudoOpSpec
{}) = spec o
166 sec s
= "\n-- * " ++ escape
(title s
) ++ "\n"
167 ++ (unlines $ map ("-- " ++ ) $ lines $ unlatex
$ escape
$ "|" ++ desc s
) ++ "\n"
169 spec o
= comm
: decls
170 where decls
= case o
of
171 PrimOpSpec
{ name
= n
, ty
= t
, opts
= options
} ->
172 [ pprFixity fixity n | OptionFixity
(Just fixity
) <- options
]
174 [ wrapOp n
++ " :: " ++ pprTy t
,
175 wrapOp n
++ " = let x = x in x" ]
176 PseudoOpSpec
{ name
= n
, ty
= t
} ->
177 [ wrapOp n
++ " :: " ++ pprTy t
,
178 wrapOp n
++ " = let x = x in x" ]
179 PrimTypeSpec
{ ty
= t
} ->
180 [ "data " ++ pprTy t
]
181 PrimClassSpec
{ cls
= t
} ->
182 [ "class " ++ pprTy t
]
185 comm
= case (desc o
) of
187 d
-> "\n" ++ (unlines $ map ("-- " ++ ) $ lines $ unlatex
$ escape
$ "|" ++ d
)
189 wrapOp nm |
isAlpha (head nm
) = nm
190 |
otherwise = "(" ++ nm
++ ")"
191 wrapTy nm |
isAlpha (head nm
) = nm
192 |
otherwise = "(" ++ nm
++ ")"
193 unlatex s
= case s
of
194 '\\':'t
':'e
':'x
':'t
':'t
':'t
':'{':cs
-> markup
"@" "@" cs
195 '{':'\\':'t
':'t
':cs
-> markup
"@" "@" cs
196 '{':'\\':'i
':'t
':cs
-> markup
"/" "/" cs
197 c
: cs
-> c
: unlatex cs
199 markup s t xs
= s
++ mk
(dropWhile isSpace xs
)
201 mk
('\n':cs
) = ' ' : mk cs
202 mk
('}':cs
) = t
++ unlatex cs
203 mk
(c
:cs
) = c
: mk cs
204 escape
= concatMap (\c
-> if c `
elem` special
then '\\':c
:[] else c
:[])
205 where special
= "/'`\"@<"
207 pprFixity
(Fixity i d
) n
= pprFixityDir d
++ " " ++ show i
++ " " ++ n
209 pprTy
:: Ty
-> String
212 pty
(TyF t1 t2
) = pbty t1
++ " -> " ++ pty t2
213 pty
(TyC t1 t2
) = pbty t1
++ " => " ++ pty t2
215 pbty
(TyApp tc ts
) = tc
++ concat (map (' ' :) (map paty ts
))
216 pbty
(TyUTup ts
) = "(# "
217 ++ concat (intersperse "," (map pty ts
))
222 paty t
= "(" ++ pty t
++ ")"
224 -- Generates the type environment that the stand-alone External Core tools use.
225 gen_ext_core_source
:: [Entry
] -> String
226 gen_ext_core_source entries
=
227 "-----------------------------------------------------------------------\n"
228 ++ "-- This module is automatically generated by the GHC utility\n"
229 ++ "-- \"genprimopcode\". Do not edit!\n"
230 ++ "-----------------------------------------------------------------------\n"
231 ++ "module Language.Core.PrimEnv(primTcs, primVals, intLitTypes, ratLitTypes,"
232 ++ "\n charLitTypes, stringLitTypes) where\nimport Language.Core.Core"
233 ++ "\nimport Language.Core.Encoding\n\n"
234 ++ "primTcs :: [(Tcon, Kind)]\n"
236 ++ printList tcEnt entries
238 ++ "primVals :: [(Var, Ty)]\n"
240 ++ printList valEnt entries
242 ++ "intLitTypes :: [Ty]\n"
243 ++ "intLitTypes = [\n"
244 ++ printList tyEnt
(intLitTys entries
)
246 ++ "ratLitTypes :: [Ty]\n"
247 ++ "ratLitTypes = [\n"
248 ++ printList tyEnt
(ratLitTys entries
)
250 ++ "charLitTypes :: [Ty]\n"
251 ++ "charLitTypes = [\n"
252 ++ printList tyEnt
(charLitTys entries
)
254 ++ "stringLitTypes :: [Ty]\n"
255 ++ "stringLitTypes = [\n"
256 ++ printList tyEnt
(stringLitTys entries
)
259 where printList f
= concat . intersperse ",\n" . filter (not . null) . map f
260 tcEnt
(PrimTypeSpec
{ty
=t
}) =
262 TyApp tc args
-> parens tc
(tcKind tc args
)
263 _
-> error ("tcEnt: type in PrimTypeSpec is not a type"
264 ++ " constructor: " ++ show t
)
267 -- The primops.txt.pp format doesn't have enough information in it to
268 -- print out some of the information that ext-core needs (like kinds,
269 -- and later on in this code, module names) so we special-case. An
270 -- alternative would be to refer to things indirectly and hard-wire
271 -- certain things (e.g., the kind of the Any constructor, here) into
272 -- ext-core's Prims module again.
273 tcKind
"Any" _
= "Klifted"
274 tcKind tc
[] |
last tc
== '#' = "Kunlifted"
275 tcKind _
[] |
otherwise = "Klifted"
276 -- assumes that all type arguments are lifted (are they?)
277 tcKind tc
(_v
:as) = "(Karrow Klifted " ++ tcKind tc
as
279 valEnt
(PseudoOpSpec
{name
=n
, ty
=t
}) = valEntry n t
280 valEnt
(PrimOpSpec
{name
=n
, ty
=t
}) = valEntry n t
282 valEntry name
' ty
' = parens name
' (mkForallTy
(freeTvars ty
') (pty ty
'))
283 where pty
(TyF t1 t2
) = mkFunTy
(pty t1
) (pty t2
)
284 pty
(TyC t1 t2
) = mkFunTy
(pty t1
) (pty t2
)
285 pty
(TyApp tc ts
) = mkTconApp
(mkTcon tc
) (map pty ts
)
286 pty
(TyUTup ts
) = mkUtupleTy
(map pty ts
)
287 pty
(TyVar tv
) = paren
$ "Tvar \"" ++ tv
++ "\""
289 mkFunTy s1 s2
= "Tapp " ++ (paren
("Tapp (Tcon tcArrow)"
292 mkTconApp tc args
= foldl tapp tc args
293 mkTcon tc
= paren
$ "Tcon " ++ paren
(qualify
True tc
)
294 mkUtupleTy args
= foldl tapp
(tcUTuple
(length args
)) args
296 mkForallTy vs t
= foldr
297 (\ v s
-> "Tforall " ++
298 (paren
(quote v
++ ", " ++ vKind v
)) ++ " "
305 freeTvars
(TyF t1 t2
) = freeTvars t1 `
union` freeTvars t2
306 freeTvars
(TyC t1 t2
) = freeTvars t1 `
union` freeTvars t2
307 freeTvars
(TyApp _ tys
) = freeTvarss tys
308 freeTvars
(TyVar v
) = [v
]
309 freeTvars
(TyUTup tys
) = freeTvarss tys
310 freeTvarss
= nub . concatMap freeTvars
312 tapp s nextArg
= paren
$ "Tapp " ++ s
++ " " ++ paren nextArg
313 tcUTuple n
= paren
$ "Tcon " ++ paren
(qualify
False $ "Z"
316 tyEnt
(PrimTypeSpec
{ty
=(TyApp tc _args
)}) = " " ++ paren
("Tcon " ++
317 (paren
(qualify
True tc
)))
320 -- more hacks. might be better to do this on the ext-core side,
321 -- as per earlier comment
322 qualify _ tc | tc
== "Bool" = "Just boolMname" ++ ", "
324 qualify _ tc | tc
== "()" = "Just baseMname" ++ ", "
326 qualify enc tc
= "Just primMname" ++ ", " ++ (ze enc tc
)
327 ze enc tc
= (if enc
then "zEncodeString " else "")
328 ++ "\"" ++ tc
++ "\""
330 intLitTys
= prefixes
["Int", "Word", "Addr", "Char"]
331 ratLitTys
= prefixes
["Float", "Double"]
332 charLitTys
= prefixes
["Char"]
333 stringLitTys
= prefixes
["Addr"]
334 prefixes ps
= filter (\ t
->
336 (PrimTypeSpec
{ty
=(TyApp tc _args
)}) ->
337 any (\ p
-> p `
isPrefixOf` tc
) ps
340 parens n ty
' = " (zEncodeString \"" ++ n
++ "\", " ++ ty
' ++ ")"
341 paren s
= "(" ++ s
++ ")"
342 quote s
= "\"" ++ s
++ "\""
344 gen_latex_doc
:: Info
-> String
345 gen_latex_doc
(Info defaults entries
)
346 = "\\primopdefaults{"
347 ++ mk_options defaults
349 ++ (concat (map mk_entry entries
))
350 where mk_entry
(PrimOpSpec
{cons
=constr
,name
=n
,ty
=t
,cat
=c
,desc
=d
,opts
=o
}) =
352 ++ latex_encode constr
++ "}{"
353 ++ latex_encode n
++ "}{"
354 ++ latex_encode
(zencode n
) ++ "}{"
355 ++ latex_encode
(show c
) ++ "}{"
356 ++ latex_encode
(mk_source_ty t
) ++ "}{"
357 ++ latex_encode
(mk_core_ty t
) ++ "}{"
361 mk_entry
(Section
{title
=ti
,desc
=d
}) =
363 ++ latex_encode ti
++ "}{"
365 mk_entry
(PrimTypeSpec
{ty
=t
,desc
=d
,opts
=o
}) =
367 ++ latex_encode
(mk_source_ty t
) ++ "}{"
368 ++ latex_encode
(mk_core_ty t
) ++ "}{"
372 mk_entry
(PrimClassSpec
{cls
=t
,desc
=d
,opts
=o
}) =
374 ++ latex_encode
(mk_source_ty t
) ++ "}{"
375 ++ latex_encode
(mk_core_ty t
) ++ "}{"
379 mk_entry
(PseudoOpSpec
{name
=n
,ty
=t
,desc
=d
,opts
=o
}) =
381 ++ latex_encode
(zencode n
) ++ "}{"
382 ++ latex_encode
(mk_source_ty t
) ++ "}{"
383 ++ latex_encode
(mk_core_ty t
) ++ "}{"
387 mk_source_ty typ
= pty typ
388 where pty
(TyF t1 t2
) = pbty t1
++ " -> " ++ pty t2
389 pty
(TyC t1 t2
) = pbty t1
++ " => " ++ pty t2
391 pbty
(TyApp tc ts
) = tc
++ (concat (map (' ':) (map paty ts
)))
392 pbty
(TyUTup ts
) = "(# " ++ (concat (intersperse "," (map pty ts
))) ++ " #)"
395 paty t
= "(" ++ pty t
++ ")"
397 mk_core_ty typ
= foralls
++ (pty typ
)
398 where pty
(TyF t1 t2
) = pbty t1
++ " -> " ++ pty t2
399 pty
(TyC t1 t2
) = pbty t1
++ " => " ++ pty t2
401 pbty
(TyApp tc ts
) = (zencode tc
) ++ (concat (map (' ':) (map paty ts
)))
402 pbty
(TyUTup ts
) = (zencode
(utuplenm
(length ts
))) ++ (concat ((map (' ':) (map paty ts
))))
404 paty
(TyVar tv
) = zencode tv
405 paty
(TyApp tc
[]) = zencode tc
406 paty t
= "(" ++ pty t
++ ")"
408 utuplenm n
= "(#" ++ (replicate (n
-1) ',') ++ "#)"
409 foralls
= if tvars
== [] then "" else "%forall " ++ (tbinds tvars
)
412 tbinds
("o":tbs
) = "(o::?) " ++ (tbinds tbs
)
413 tbinds
(tv
:tbs
) = tv
++ " " ++ (tbinds tbs
)
414 tvars_of
(TyF t1 t2
) = tvars_of t1 `
union` tvars_of t2
415 tvars_of
(TyC t1 t2
) = tvars_of t1 `
union` tvars_of t2
416 tvars_of
(TyApp _ ts
) = foldl union [] (map tvars_of ts
)
417 tvars_of
(TyUTup ts
) = foldr union [] (map tvars_of ts
)
418 tvars_of
(TyVar tv
) = [tv
]
422 ++ mk_has_side_effects o
++ "}{"
423 ++ mk_out_of_line o
++ "}{"
424 ++ mk_commutable o
++ "}{"
425 ++ mk_needs_wrapper o
++ "}{"
426 ++ mk_can_fail o
++ "}{"
427 ++ mk_fixity o
++ "}{"
428 ++ latex_encode
(mk_strictness o
) ++ "}{"
431 mk_has_side_effects o
= mk_bool_opt o
"has_side_effects" "Has side effects." "Has no side effects."
432 mk_out_of_line o
= mk_bool_opt o
"out_of_line" "Implemented out of line." "Implemented in line."
433 mk_commutable o
= mk_bool_opt o
"commutable" "Commutable." "Not commutable."
434 mk_needs_wrapper o
= mk_bool_opt o
"needs_wrapper" "Needs wrapper." "Needs no wrapper."
435 mk_can_fail o
= mk_bool_opt o
"can_fail" "Can fail." "Cannot fail."
437 mk_bool_opt o opt_name if_true if_false
=
438 case lookup_attrib opt_name o
of
439 Just
(OptionTrue _
) -> if_true
440 Just
(OptionFalse _
) -> if_false
441 Just
(OptionString _ _
) -> error "String value for boolean option"
442 Just
(OptionInteger _ _
) -> error "Integer value for boolean option"
443 Just
(OptionFixity _
) -> error "Fixity value for boolean option"
447 case lookup_attrib
"strictness" o
of
448 Just
(OptionString _ s
) -> s
-- for now
449 Just _
-> error "Wrong value for strictness"
452 mk_fixity o
= case lookup_attrib
"fixity" o
of
453 Just
(OptionFixity
(Just
(Fixity i d
)))
454 -> pprFixityDir d
++ " " ++ show i
458 case maybe_tuple xs
of
459 Just n
-> n
-- Tuples go to Z2T etc
460 Nothing
-> concat (map encode_ch xs
)
462 maybe_tuple
"(# #)" = Just
("Z1H")
463 maybe_tuple
('(' : '#' : cs
) = case count_commas
(0::Int) cs
of
464 (n
, '#' : ')' : _
) -> Just
('Z
' : shows (n
+1) "H")
466 maybe_tuple
"()" = Just
("Z0T")
467 maybe_tuple
('(' : cs
) = case count_commas
(0::Int) cs
of
468 (n
, ')' : _
) -> Just
('Z
' : shows (n
+1) "T")
470 maybe_tuple _
= Nothing
472 count_commas
:: Int -> String -> (Int, String)
473 count_commas n
(',' : cs
) = count_commas
(n
+1) cs
474 count_commas n cs
= (n
,cs
)
476 unencodedChar
:: Char -> Bool -- True for chars that don't need encoding
477 unencodedChar
'Z
' = False
478 unencodedChar
'z
' = False
479 unencodedChar c
= isAlphaNum c
481 encode_ch
:: Char -> String
482 encode_ch c | unencodedChar c
= [c
] -- Common case first
485 encode_ch
'(' = "ZL" -- Needed for things like (,), and (->)
486 encode_ch
')' = "ZR" -- For symmetry with (
506 encode_ch
'\'' = "zq"
507 encode_ch
'\\' = "zr"
512 encode_ch c
= 'z
' : shows (ord c
) "U"
515 latex_encode
(c
:cs
) | c `
elem`
"#$%&_^{}" = "\\" ++ c
:(latex_encode cs
)
516 latex_encode
('~
':cs
) = "\\verb!~!" ++ (latex_encode cs
)
517 latex_encode
('\\':cs
) = "$\\backslash$" ++ (latex_encode cs
)
518 latex_encode
(c
:cs
) = c
:(latex_encode cs
)
520 gen_wrappers
:: Info
-> String
521 gen_wrappers
(Info _ entries
)
522 = "{-# LANGUAGE CPP, NoImplicitPrelude, UnboxedTuples #-}\n"
523 -- Dependencies on Prelude must be explicit in libraries/base, but we
524 -- don't need the Prelude here so we add NoImplicitPrelude.
525 ++ "module GHC.PrimopWrappers where\n"
526 ++ "import qualified GHC.Prim\n"
527 ++ "import GHC.Tuple ()\n"
528 ++ "import GHC.Prim (" ++ concat (intersperse ", " othertycons
) ++ ")\n"
529 ++ "#if defined (__GLASGOW_HASKELL_LLVM__)\n"
530 ++ "import GHC.Prim (" ++ concat (intersperse ", " vectycons
) ++ ")\n"
531 ++ "#endif /* defined (__GLASGOW_HASKELL_LLVM__) */\n"
532 ++ unlines (concatMap f otherspecs
)
533 ++ "#if defined (__GLASGOW_HASKELL_LLVM__)\n"
534 ++ unlines (concatMap f vecspecs
)
535 ++ "#endif /* defined (__GLASGOW_HASKELL_LLVM__) */\n"
537 specs
= filter (not.dodgy
) (filter is_primop entries
)
538 (vecspecs
, otherspecs
) = partition is_llvm_only specs
539 tycons
= foldr union [] $ map (tyconsIn
. ty
) specs
540 (vectycons
, othertycons
) =
541 (partition llvmOnlyTyCon
. filter (`
notElem`
["()", "Bool"])) tycons
542 f spec
= let args
= map (\n -> "a" ++ show n
) [1 .. arity
(ty spec
)]
543 src_name
= wrap
(name spec
)
544 lhs
= src_name
++ " " ++ unwords args
545 rhs
= "(GHC.Prim." ++ name spec
++ ") " ++ unwords args
546 in ["{-# NOINLINE " ++ src_name
++ " #-}",
547 src_name
++ " :: " ++ pprTy
(ty spec
),
549 wrap nm |
isLower (head nm
) = nm
550 |
otherwise = "(" ++ nm
++ ")"
554 [-- C code generator can't handle these
557 -- not interested in parallel support
558 "par#", "parGlobal#", "parLocal#", "parAt#",
559 "parAtAbs#", "parAtRel#", "parAtForNow#"
562 is_llvm_only
:: Entry
-> Bool
564 case lookup_attrib
"llvm_only" (opts entry
) of
565 Just
(OptionTrue _
) -> True
568 llvmOnlyTyCon
:: TyCon
-> Bool
569 llvmOnlyTyCon
"Int32#" = True
570 llvmOnlyTyCon
"FloatX4#" = True
571 llvmOnlyTyCon
"DoubleX2#" = True
572 llvmOnlyTyCon
"Int32X4#" = True
573 llvmOnlyTyCon
"Int64X2#" = True
574 llvmOnlyTyCon _
= False
576 gen_primop_list
:: Info
-> String
577 gen_primop_list
(Info _ entries
)
579 [ " [" ++ cons first
]
581 map (\p
-> " , " ++ cons p
) rest
584 ) where (first
:rest
) = filter is_primop entries
586 gen_primop_tag
:: Info
-> String
587 gen_primop_tag
(Info _ entries
)
588 = unlines (max_def_type
: max_def
:
589 tagOf_type
: zipWith f primop_entries
[1 :: Int ..])
591 primop_entries
= filter is_primop entries
592 tagOf_type
= "tagOf_PrimOp :: PrimOp -> FastInt"
593 f i n
= "tagOf_PrimOp " ++ cons i
++ " = _ILIT(" ++ show n
++ ")"
594 max_def_type
= "maxPrimOpTag :: Int"
595 max_def
= "maxPrimOpTag = " ++ show (length primop_entries
)
597 gen_data_decl
:: Info
-> String
598 gen_data_decl
(Info _ entries
)
599 = let conss
= map cons
(filter is_primop entries
)
600 in "data PrimOp\n = " ++ head conss
++ "\n"
601 ++ unlines (map (" | "++) (tail conss
))
603 gen_switch_from_attribs
:: String -> String -> Info
-> String
604 gen_switch_from_attribs attrib_name fn_name
(Info defaults entries
)
605 = let defv
= lookup_attrib attrib_name defaults
606 alternatives
= catMaybes (map mkAlt
(filter is_primop entries
))
608 getAltRhs
(OptionFalse _
) = "False"
609 getAltRhs
(OptionTrue _
) = "True"
610 getAltRhs
(OptionInteger _ i
) = show i
611 getAltRhs
(OptionString _ s
) = s
612 getAltRhs
(OptionFixity mf
) = show mf
615 = case lookup_attrib attrib_name
(opts po
) of
617 Just xx
-> Just
(fn_name
++ " " ++ cons po
++ " = " ++ getAltRhs xx
)
621 Nothing
-> error ("gen_switch_from: " ++ attrib_name
)
623 -> unlines alternatives
624 ++ fn_name
++ " _ = " ++ getAltRhs xx
++ "\n"
626 ------------------------------------------------------------------
627 -- Create PrimOpInfo text from PrimOpSpecs -----------------------
628 ------------------------------------------------------------------
630 gen_primop_info
:: Info
-> String
631 gen_primop_info
(Info _ entries
)
632 = unlines (map mkPOItext
(filter is_primop entries
))
634 mkPOItext
:: Entry
-> String
635 mkPOItext i
= mkPOI_LHS_text i
++ mkPOI_RHS_text i
637 mkPOI_LHS_text
:: Entry
-> String
639 = "primOpInfo " ++ cons i
++ " = "
641 mkPOI_RHS_text
:: Entry
-> String
647 -> "mkCompare " ++ sl_name i
++ ppType t1
648 _
-> error "Type error in comparison op"
652 -> "mkMonadic " ++ sl_name i
++ ppType t1
653 _
-> error "Type error in monadic op"
657 -> "mkDyadic " ++ sl_name i
++ ppType t1
658 _
-> error "Type error in dyadic op"
660 -> let (argTys
, resTy
) = flatTys
(ty i
)
661 tvs
= nub (tvsIn
(ty i
))
663 "mkGenPrimOp " ++ sl_name i
++ " "
664 ++ listify
(map ppTyVar tvs
) ++ " "
665 ++ listify
(map ppType argTys
) ++ " "
666 ++ "(" ++ ppType resTy
++ ")"
668 sl_name
:: Entry
-> String
669 sl_name i
= "(fsLit \"" ++ name i
++ "\") "
671 ppTyVar
:: String -> String
672 ppTyVar
"a" = "alphaTyVar"
673 ppTyVar
"b" = "betaTyVar"
674 ppTyVar
"c" = "gammaTyVar"
675 ppTyVar
"s" = "deltaTyVar"
676 ppTyVar
"o" = "openAlphaTyVar"
677 ppTyVar _
= error "Unknown type var"
679 ppType
:: Ty
-> String
680 ppType
(TyApp
"Any" []) = "anyTy"
681 ppType
(TyApp
"Bool" []) = "boolTy"
683 ppType
(TyApp
"Int#" []) = "intPrimTy"
684 ppType
(TyApp
"Int32#" []) = "int32PrimTy"
685 ppType
(TyApp
"Int64#" []) = "int64PrimTy"
686 ppType
(TyApp
"Char#" []) = "charPrimTy"
687 ppType
(TyApp
"Word#" []) = "wordPrimTy"
688 ppType
(TyApp
"Word32#" []) = "word32PrimTy"
689 ppType
(TyApp
"Word64#" []) = "word64PrimTy"
690 ppType
(TyApp
"Addr#" []) = "addrPrimTy"
691 ppType
(TyApp
"Float#" []) = "floatPrimTy"
692 ppType
(TyApp
"Double#" []) = "doublePrimTy"
693 ppType
(TyApp
"FloatX4#" []) = "floatX4PrimTy"
694 ppType
(TyApp
"DoubleX2#" []) = "doubleX2PrimTy"
695 ppType
(TyApp
"Int32X4#" []) = "int32X4PrimTy"
696 ppType
(TyApp
"Int64X2#" []) = "int64X2PrimTy"
697 ppType
(TyApp
"ByteArray#" []) = "byteArrayPrimTy"
698 ppType
(TyApp
"RealWorld" []) = "realWorldTy"
699 ppType
(TyApp
"ThreadId#" []) = "threadIdPrimTy"
700 ppType
(TyApp
"ForeignObj#" []) = "foreignObjPrimTy"
701 ppType
(TyApp
"BCO#" []) = "bcoPrimTy"
702 ppType
(TyApp
"()" []) = "unitTy" -- unitTy is TysWiredIn's name for ()
704 ppType
(TyVar
"a") = "alphaTy"
705 ppType
(TyVar
"b") = "betaTy"
706 ppType
(TyVar
"c") = "gammaTy"
707 ppType
(TyVar
"s") = "deltaTy"
708 ppType
(TyVar
"o") = "openAlphaTy"
710 ppType
(TyApp
"State#" [x
]) = "mkStatePrimTy " ++ ppType x
711 ppType
(TyApp
"MutVar#" [x
,y
]) = "mkMutVarPrimTy " ++ ppType x
713 ppType
(TyApp
"MutableArray#" [x
,y
]) = "mkMutableArrayPrimTy " ++ ppType x
715 ppType
(TyApp
"MutableArrayArray#" [x
]) = "mkMutableArrayArrayPrimTy " ++ ppType x
716 ppType
(TyApp
"MutableByteArray#" [x
]) = "mkMutableByteArrayPrimTy "
718 ppType
(TyApp
"Array#" [x
]) = "mkArrayPrimTy " ++ ppType x
719 ppType
(TyApp
"ArrayArray#" []) = "mkArrayArrayPrimTy"
722 ppType
(TyApp
"Weak#" [x
]) = "mkWeakPrimTy " ++ ppType x
723 ppType
(TyApp
"StablePtr#" [x
]) = "mkStablePtrPrimTy " ++ ppType x
724 ppType
(TyApp
"StableName#" [x
]) = "mkStableNamePrimTy " ++ ppType x
726 ppType
(TyApp
"MVar#" [x
,y
]) = "mkMVarPrimTy " ++ ppType x
728 ppType
(TyApp
"TVar#" [x
,y
]) = "mkTVarPrimTy " ++ ppType x
730 ppType
(TyUTup ts
) = "(mkTupleTy UnboxedTuple "
731 ++ listify
(map ppType ts
) ++ ")"
733 ppType
(TyF s d
) = "(mkFunTy (" ++ ppType s
++ ") (" ++ ppType d
++ "))"
734 ppType
(TyC s d
) = "(mkFunTy (" ++ ppType s
++ ") (" ++ ppType d
++ "))"
737 = error ("ppType: can't handle: " ++ show other
++ "\n")
739 pprFixityDir
:: FixityDirection
-> String
740 pprFixityDir InfixN
= "infix"
741 pprFixityDir InfixL
= "infixl"
742 pprFixityDir InfixR
= "infixr"
744 listify
:: [String] -> String
745 listify ss
= "[" ++ concat (intersperse ", " ss
) ++ "]"
747 flatTys
:: Ty
-> ([Ty
],Ty
)
748 flatTys
(TyF t1 t2
) = case flatTys t2
of (ts
,t
) -> (t1
:ts
,t
)
749 flatTys
(TyC t1 t2
) = case flatTys t2
of (ts
,t
) -> (t1
:ts
,t
)
750 flatTys other
= ([],other
)
752 tvsIn
:: Ty
-> [TyVar
]
753 tvsIn
(TyF t1 t2
) = tvsIn t1
++ tvsIn t2
754 tvsIn
(TyC t1 t2
) = tvsIn t1
++ tvsIn t2
755 tvsIn
(TyApp _ tys
) = concatMap tvsIn tys
756 tvsIn
(TyVar tv
) = [tv
]
757 tvsIn
(TyUTup tys
) = concatMap tvsIn tys
759 tyconsIn
:: Ty
-> [TyCon
]
760 tyconsIn
(TyF t1 t2
) = tyconsIn t1 `
union` tyconsIn t2
761 tyconsIn
(TyC t1 t2
) = tyconsIn t1 `
union` tyconsIn t2
762 tyconsIn
(TyApp tc tys
) = foldr union [tc
] $ map tyconsIn tys
763 tyconsIn
(TyVar _
) = []
764 tyconsIn
(TyUTup tys
) = foldr union [] $ map tyconsIn tys
767 arity
= length . fst . flatTys