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
)
64 "--primop-primop-info"
65 -> putStr (gen_primop_info p_o_specs
)
68 -> putStr (gen_primop_tag p_o_specs
)
71 -> putStr (gen_primop_list p_o_specs
)
73 "--make-haskell-wrappers"
74 -> putStr (gen_wrappers p_o_specs
)
76 "--make-haskell-source"
77 -> putStr (gen_hs_source p_o_specs
)
79 "--make-ext-core-source"
80 -> putStr (gen_ext_core_source entries
)
83 -> putStr (gen_latex_doc p_o_specs
)
85 _
-> error "Should not happen, known_args out of sync?"
88 known_args
:: [String]
97 "--primop-primop-info",
100 "--make-haskell-wrappers",
101 "--make-haskell-source",
102 "--make-ext-core-source",
106 ------------------------------------------------------------------
107 -- Code generators -----------------------------------------------
108 ------------------------------------------------------------------
110 gen_hs_source
:: Info
-> String
111 gen_hs_source
(Info defaults entries
) =
113 ++ "This is a generated file (generated by genprimopcode).\n"
114 ++ "It is not code to actually be used. Its only purpose is to be\n"
115 ++ "consumed by haddock.\n"
118 ++ "-----------------------------------------------------------------------------\n"
120 ++ "-- Module : GHC.Prim\n"
122 ++ "-- Maintainer : cvs-ghc@haskell.org\n"
123 ++ "-- Stability : internal\n"
124 ++ "-- Portability : non-portable (GHC extensions)\n"
126 ++ "-- GHC\'s primitive types and operations.\n"
127 ++ "-- Use GHC.Exts from the base package instead of importing this\n"
128 ++ "-- module directly.\n"
130 ++ "-----------------------------------------------------------------------------\n"
131 ++ "module GHC.Prim (\n"
132 ++ unlines (map (("\t" ++) . hdr
) entries
)
135 ++ "import GHC.Types\n"
138 ++ unlines (map opt defaults
)
140 ++ unlines (concatMap ent entries
) ++ "\n\n\n"
141 where opt
(OptionFalse n
) = n
++ " = False"
142 opt
(OptionTrue n
) = n
++ " = True"
143 opt
(OptionString n v
) = n
++ " = { " ++ v
++ "}"
144 opt
(OptionInteger n v
) = n
++ " = " ++ show v
146 hdr s
@(Section
{}) = sec s
147 hdr
(PrimOpSpec
{ name
= n
}) = wrapOp n
++ ","
148 hdr
(PseudoOpSpec
{ name
= n
}) = wrapOp n
++ ","
149 hdr
(PrimTypeSpec
{ ty
= TyApp n _
}) = wrapTy n
++ ","
150 hdr
(PrimTypeSpec
{}) = error "Illegal type spec"
152 ent
(Section
{}) = []
153 ent o
@(PrimOpSpec
{}) = spec o
154 ent o
@(PrimTypeSpec
{}) = spec o
155 ent o
@(PseudoOpSpec
{}) = spec o
157 sec s
= "\n-- * " ++ escape
(title s
) ++ "\n"
158 ++ (unlines $ map ("-- " ++ ) $ lines $ unlatex
$ escape
$ "|" ++ desc s
) ++ "\n"
160 spec o
= comm
: decls
161 where decls
= case o
of
162 PrimOpSpec
{ name
= n
, ty
= t
} ->
163 [ wrapOp n
++ " :: " ++ pprTy t
,
164 wrapOp n
++ " = let x = x in x" ]
165 PseudoOpSpec
{ name
= n
, ty
= t
} ->
166 [ wrapOp n
++ " :: " ++ pprTy t
,
167 wrapOp n
++ " = let x = x in x" ]
168 PrimTypeSpec
{ ty
= t
} ->
169 [ "data " ++ pprTy t
]
172 comm
= case (desc o
) of
174 d
-> "\n" ++ (unlines $ map ("-- " ++ ) $ lines $ unlatex
$ escape
$ "|" ++ d
)
176 wrapOp nm |
isAlpha (head nm
) = nm
177 |
otherwise = "(" ++ nm
++ ")"
178 wrapTy nm |
isAlpha (head nm
) = nm
179 |
otherwise = "(" ++ nm
++ ")"
180 unlatex s
= case s
of
181 '\\':'t
':'e
':'x
':'t
':'t
':'t
':'{':cs
-> markup
"@" "@" cs
182 '{':'\\':'t
':'t
':cs
-> markup
"@" "@" cs
183 '{':'\\':'i
':'t
':cs
-> markup
"/" "/" cs
184 c
: cs
-> c
: unlatex cs
186 markup s t xs
= s
++ mk
(dropWhile isSpace xs
)
188 mk
('\n':cs
) = ' ' : mk cs
189 mk
('}':cs
) = t
++ unlatex cs
190 mk
(c
:cs
) = c
: mk cs
191 escape
= concatMap (\c
-> if c `
elem` special
then '\\':c
:[] else c
:[])
192 where special
= "/'`\"@<"
194 pprTy
:: Ty
-> String
197 pty
(TyF t1 t2
) = pbty t1
++ " -> " ++ pty t2
199 pbty
(TyApp tc ts
) = tc
++ concat (map (' ' :) (map paty ts
))
200 pbty
(TyUTup ts
) = "(# "
201 ++ concat (intersperse "," (map pty ts
))
206 paty t
= "(" ++ pty t
++ ")"
208 -- Generates the type environment that the stand-alone External Core tools use.
209 gen_ext_core_source
:: [Entry
] -> String
210 gen_ext_core_source entries
=
211 "-----------------------------------------------------------------------\n"
212 ++ "-- This module is automatically generated by the GHC utility\n"
213 ++ "-- \"genprimopcode\". Do not edit!\n"
214 ++ "-----------------------------------------------------------------------\n"
215 ++ "module Language.Core.PrimEnv(primTcs, primVals, intLitTypes, ratLitTypes,"
216 ++ "\n charLitTypes, stringLitTypes) where\nimport Language.Core.Core"
217 ++ "\nimport Language.Core.Encoding\n\n"
218 ++ "primTcs :: [(Tcon, Kind)]\n"
220 ++ printList tcEnt entries
222 ++ "primVals :: [(Var, Ty)]\n"
224 ++ printList valEnt entries
226 ++ "intLitTypes :: [Ty]\n"
227 ++ "intLitTypes = [\n"
228 ++ printList tyEnt
(intLitTys entries
)
230 ++ "ratLitTypes :: [Ty]\n"
231 ++ "ratLitTypes = [\n"
232 ++ printList tyEnt
(ratLitTys entries
)
234 ++ "charLitTypes :: [Ty]\n"
235 ++ "charLitTypes = [\n"
236 ++ printList tyEnt
(charLitTys entries
)
238 ++ "stringLitTypes :: [Ty]\n"
239 ++ "stringLitTypes = [\n"
240 ++ printList tyEnt
(stringLitTys entries
)
243 where printList f
= concat . intersperse ",\n" . filter (not . null) . map f
244 tcEnt
(PrimTypeSpec
{ty
=t
}) =
246 TyApp tc args
-> parens tc
(tcKind tc args
)
247 _
-> error ("tcEnt: type in PrimTypeSpec is not a type"
248 ++ " constructor: " ++ show t
)
251 -- The primops.txt.pp format doesn't have enough information in it to
252 -- print out some of the information that ext-core needs (like kinds,
253 -- and later on in this code, module names) so we special-case. An
254 -- alternative would be to refer to things indirectly and hard-wire
255 -- certain things (e.g., the kind of the Any constructor, here) into
256 -- ext-core's Prims module again.
257 tcKind
"Any" _
= "Klifted"
258 tcKind tc
[] |
last tc
== '#' = "Kunlifted"
259 tcKind _
[] |
otherwise = "Klifted"
260 -- assumes that all type arguments are lifted (are they?)
261 tcKind tc
(_v
:as) = "(Karrow Klifted " ++ tcKind tc
as
263 valEnt
(PseudoOpSpec
{name
=n
, ty
=t
}) = valEntry n t
264 valEnt
(PrimOpSpec
{name
=n
, ty
=t
}) = valEntry n t
266 valEntry name
' ty
' = parens name
' (mkForallTy
(freeTvars ty
') (pty ty
'))
267 where pty
(TyF t1 t2
) = mkFunTy
(pty t1
) (pty t2
)
268 pty
(TyApp tc ts
) = mkTconApp
(mkTcon tc
) (map pty ts
)
269 pty
(TyUTup ts
) = mkUtupleTy
(map pty ts
)
270 pty
(TyVar tv
) = paren
$ "Tvar \"" ++ tv
++ "\""
272 mkFunTy s1 s2
= "Tapp " ++ (paren
("Tapp (Tcon tcArrow)"
275 mkTconApp tc args
= foldl tapp tc args
276 mkTcon tc
= paren
$ "Tcon " ++ paren
(qualify
True tc
)
277 mkUtupleTy args
= foldl tapp
(tcUTuple
(length args
)) args
279 mkForallTy vs t
= foldr
280 (\ v s
-> "Tforall " ++
281 (paren
(quote v
++ ", " ++ vKind v
)) ++ " "
288 freeTvars
(TyF t1 t2
) = freeTvars t1 `
union` freeTvars t2
289 freeTvars
(TyApp _ tys
) = freeTvarss tys
290 freeTvars
(TyVar v
) = [v
]
291 freeTvars
(TyUTup tys
) = freeTvarss tys
292 freeTvarss
= nub . concatMap freeTvars
294 tapp s nextArg
= paren
$ "Tapp " ++ s
++ " " ++ paren nextArg
295 tcUTuple n
= paren
$ "Tcon " ++ paren
(qualify
False $ "Z"
298 tyEnt
(PrimTypeSpec
{ty
=(TyApp tc _args
)}) = " " ++ paren
("Tcon " ++
299 (paren
(qualify
True tc
)))
302 -- more hacks. might be better to do this on the ext-core side,
303 -- as per earlier comment
304 qualify _ tc | tc
== "Bool" = "Just boolMname" ++ ", "
306 qualify _ tc | tc
== "()" = "Just baseMname" ++ ", "
308 qualify enc tc
= "Just primMname" ++ ", " ++ (ze enc tc
)
309 ze enc tc
= (if enc
then "zEncodeString " else "")
310 ++ "\"" ++ tc
++ "\""
312 intLitTys
= prefixes
["Int", "Word", "Addr", "Char"]
313 ratLitTys
= prefixes
["Float", "Double"]
314 charLitTys
= prefixes
["Char"]
315 stringLitTys
= prefixes
["Addr"]
316 prefixes ps
= filter (\ t
->
318 (PrimTypeSpec
{ty
=(TyApp tc _args
)}) ->
319 any (\ p
-> p `
isPrefixOf` tc
) ps
322 parens n ty
' = " (zEncodeString \"" ++ n
++ "\", " ++ ty
' ++ ")"
323 paren s
= "(" ++ s
++ ")"
324 quote s
= "\"" ++ s
++ "\""
326 gen_latex_doc
:: Info
-> String
327 gen_latex_doc
(Info defaults entries
)
328 = "\\primopdefaults{"
329 ++ mk_options defaults
331 ++ (concat (map mk_entry entries
))
332 where mk_entry
(PrimOpSpec
{cons
=constr
,name
=n
,ty
=t
,cat
=c
,desc
=d
,opts
=o
}) =
334 ++ latex_encode constr
++ "}{"
335 ++ latex_encode n
++ "}{"
336 ++ latex_encode
(zencode n
) ++ "}{"
337 ++ latex_encode
(show c
) ++ "}{"
338 ++ latex_encode
(mk_source_ty t
) ++ "}{"
339 ++ latex_encode
(mk_core_ty t
) ++ "}{"
343 mk_entry
(Section
{title
=ti
,desc
=d
}) =
345 ++ latex_encode ti
++ "}{"
347 mk_entry
(PrimTypeSpec
{ty
=t
,desc
=d
,opts
=o
}) =
349 ++ latex_encode
(mk_source_ty t
) ++ "}{"
350 ++ latex_encode
(mk_core_ty t
) ++ "}{"
354 mk_entry
(PseudoOpSpec
{name
=n
,ty
=t
,desc
=d
,opts
=o
}) =
356 ++ latex_encode
(zencode n
) ++ "}{"
357 ++ latex_encode
(mk_source_ty t
) ++ "}{"
358 ++ latex_encode
(mk_core_ty t
) ++ "}{"
362 mk_source_ty typ
= pty typ
363 where pty
(TyF t1 t2
) = pbty t1
++ " -> " ++ pty t2
365 pbty
(TyApp tc ts
) = tc
++ (concat (map (' ':) (map paty ts
)))
366 pbty
(TyUTup ts
) = "(# " ++ (concat (intersperse "," (map pty ts
))) ++ " #)"
369 paty t
= "(" ++ pty t
++ ")"
371 mk_core_ty typ
= foralls
++ (pty typ
)
372 where pty
(TyF t1 t2
) = pbty t1
++ " -> " ++ pty t2
374 pbty
(TyApp tc ts
) = (zencode tc
) ++ (concat (map (' ':) (map paty ts
)))
375 pbty
(TyUTup ts
) = (zencode
(utuplenm
(length ts
))) ++ (concat ((map (' ':) (map paty ts
))))
377 paty
(TyVar tv
) = zencode tv
378 paty
(TyApp tc
[]) = zencode tc
379 paty t
= "(" ++ pty t
++ ")"
381 utuplenm n
= "(#" ++ (replicate (n
-1) ',') ++ "#)"
382 foralls
= if tvars
== [] then "" else "%forall " ++ (tbinds tvars
)
385 tbinds
("o":tbs
) = "(o::?) " ++ (tbinds tbs
)
386 tbinds
(tv
:tbs
) = tv
++ " " ++ (tbinds tbs
)
387 tvars_of
(TyF t1 t2
) = tvars_of t1 `
union` tvars_of t2
388 tvars_of
(TyApp _ ts
) = foldl union [] (map tvars_of ts
)
389 tvars_of
(TyUTup ts
) = foldr union [] (map tvars_of ts
)
390 tvars_of
(TyVar tv
) = [tv
]
394 ++ mk_has_side_effects o
++ "}{"
395 ++ mk_out_of_line o
++ "}{"
396 ++ mk_commutable o
++ "}{"
397 ++ mk_needs_wrapper o
++ "}{"
398 ++ mk_can_fail o
++ "}{"
399 ++ latex_encode
(mk_strictness o
) ++ "}{"
402 mk_has_side_effects o
= mk_bool_opt o
"has_side_effects" "Has side effects." "Has no side effects."
403 mk_out_of_line o
= mk_bool_opt o
"out_of_line" "Implemented out of line." "Implemented in line."
404 mk_commutable o
= mk_bool_opt o
"commutable" "Commutable." "Not commutable."
405 mk_needs_wrapper o
= mk_bool_opt o
"needs_wrapper" "Needs wrapper." "Needs no wrapper."
406 mk_can_fail o
= mk_bool_opt o
"can_fail" "Can fail." "Cannot fail."
408 mk_bool_opt o opt_name if_true if_false
=
409 case lookup_attrib opt_name o
of
410 Just
(OptionTrue _
) -> if_true
411 Just
(OptionFalse _
) -> if_false
412 Just
(OptionString _ _
) -> error "String value for boolean option"
413 Just
(OptionInteger _ _
) -> error "Integer value for boolean option"
417 case lookup_attrib
"strictness" o
of
418 Just
(OptionString _ s
) -> s
-- for now
419 Just _
-> error "Boolean value for strictness"
423 case maybe_tuple xs
of
424 Just n
-> n
-- Tuples go to Z2T etc
425 Nothing
-> concat (map encode_ch xs
)
427 maybe_tuple
"(# #)" = Just
("Z1H")
428 maybe_tuple
('(' : '#' : cs
) = case count_commas
(0::Int) cs
of
429 (n
, '#' : ')' : _
) -> Just
('Z
' : shows (n
+1) "H")
431 maybe_tuple
"()" = Just
("Z0T")
432 maybe_tuple
('(' : cs
) = case count_commas
(0::Int) cs
of
433 (n
, ')' : _
) -> Just
('Z
' : shows (n
+1) "T")
435 maybe_tuple _
= Nothing
437 count_commas
:: Int -> String -> (Int, String)
438 count_commas n
(',' : cs
) = count_commas
(n
+1) cs
439 count_commas n cs
= (n
,cs
)
441 unencodedChar
:: Char -> Bool -- True for chars that don't need encoding
442 unencodedChar
'Z
' = False
443 unencodedChar
'z
' = False
444 unencodedChar c
= isAlphaNum c
446 encode_ch
:: Char -> String
447 encode_ch c | unencodedChar c
= [c
] -- Common case first
450 encode_ch
'(' = "ZL" -- Needed for things like (,), and (->)
451 encode_ch
')' = "ZR" -- For symmetry with (
471 encode_ch
'\'' = "zq"
472 encode_ch
'\\' = "zr"
477 encode_ch c
= 'z
' : shows (ord c
) "U"
480 latex_encode
(c
:cs
) | c `
elem`
"#$%&_^{}" = "\\" ++ c
:(latex_encode cs
)
481 latex_encode
('~
':cs
) = "\\verb!~!" ++ (latex_encode cs
)
482 latex_encode
('\\':cs
) = "$\\backslash$" ++ (latex_encode cs
)
483 latex_encode
(c
:cs
) = c
:(latex_encode cs
)
485 gen_wrappers
:: Info
-> String
486 gen_wrappers
(Info _ entries
)
487 = "{-# LANGUAGE NoImplicitPrelude, UnboxedTuples #-}\n"
488 -- Dependencies on Prelude must be explicit in libraries/base, but we
489 -- don't need the Prelude here so we add NoImplicitPrelude.
490 ++ "module GHC.PrimopWrappers where\n"
491 ++ "import qualified GHC.Prim\n"
492 ++ "import GHC.Types (Bool)\n"
493 ++ "import GHC.Tuple ()\n"
494 ++ "import GHC.Prim (" ++ types
++ ")\n"
495 ++ unlines (concatMap f specs
)
497 specs
= filter (not.dodgy
) (filter is_primop entries
)
498 tycons
= foldr union [] $ map (tyconsIn
. ty
) specs
499 tycons
' = filter (`
notElem`
["()", "Bool"]) tycons
500 types
= concat $ intersperse ", " tycons
'
501 f spec
= let args
= map (\n -> "a" ++ show n
) [1 .. arity
(ty spec
)]
502 src_name
= wrap
(name spec
)
503 lhs
= src_name
++ " " ++ unwords args
504 rhs
= "(GHC.Prim." ++ name spec
++ ") " ++ unwords args
505 in ["{-# NOINLINE " ++ src_name
++ " #-}",
506 src_name
++ " :: " ++ pprTy
(ty spec
),
508 wrap nm |
isLower (head nm
) = nm
509 |
otherwise = "(" ++ nm
++ ")"
513 [-- C code generator can't handle these
516 -- not interested in parallel support
517 "par#", "parGlobal#", "parLocal#", "parAt#",
518 "parAtAbs#", "parAtRel#", "parAtForNow#"
521 gen_primop_list
:: Info
-> String
522 gen_primop_list
(Info _ entries
)
524 [ " [" ++ cons first
]
526 map (\p
-> " , " ++ cons p
) rest
529 ) where (first
:rest
) = filter is_primop entries
531 gen_primop_tag
:: Info
-> String
532 gen_primop_tag
(Info _ entries
)
533 = unlines (max_def_type
: max_def
:
534 tagOf_type
: zipWith f primop_entries
[1 :: Int ..])
536 primop_entries
= filter is_primop entries
537 tagOf_type
= "tagOf_PrimOp :: PrimOp -> FastInt"
538 f i n
= "tagOf_PrimOp " ++ cons i
++ " = _ILIT(" ++ show n
++ ")"
539 max_def_type
= "maxPrimOpTag :: Int"
540 max_def
= "maxPrimOpTag = " ++ show (length primop_entries
)
542 gen_data_decl
:: Info
-> String
543 gen_data_decl
(Info _ entries
)
544 = let conss
= map cons
(filter is_primop entries
)
545 in "data PrimOp\n = " ++ head conss
++ "\n"
546 ++ unlines (map (" | "++) (tail conss
))
548 gen_switch_from_attribs
:: String -> String -> Info
-> String
549 gen_switch_from_attribs attrib_name fn_name
(Info defaults entries
)
550 = let defv
= lookup_attrib attrib_name defaults
551 alternatives
= catMaybes (map mkAlt
(filter is_primop entries
))
553 getAltRhs
(OptionFalse _
) = "False"
554 getAltRhs
(OptionTrue _
) = "True"
555 getAltRhs
(OptionInteger _ i
) = show i
556 getAltRhs
(OptionString _ s
) = s
559 = case lookup_attrib attrib_name
(opts po
) of
561 Just xx
-> Just
(fn_name
++ " " ++ cons po
++ " = " ++ getAltRhs xx
)
565 Nothing
-> error ("gen_switch_from: " ++ attrib_name
)
567 -> unlines alternatives
568 ++ fn_name
++ " _ = " ++ getAltRhs xx
++ "\n"
570 ------------------------------------------------------------------
571 -- Create PrimOpInfo text from PrimOpSpecs -----------------------
572 ------------------------------------------------------------------
574 gen_primop_info
:: Info
-> String
575 gen_primop_info
(Info _ entries
)
576 = unlines (map mkPOItext
(filter is_primop entries
))
578 mkPOItext
:: Entry
-> String
579 mkPOItext i
= mkPOI_LHS_text i
++ mkPOI_RHS_text i
581 mkPOI_LHS_text
:: Entry
-> String
583 = "primOpInfo " ++ cons i
++ " = "
585 mkPOI_RHS_text
:: Entry
-> String
591 -> "mkCompare " ++ sl_name i
++ ppType t1
592 _
-> error "Type error in comparison op"
596 -> "mkMonadic " ++ sl_name i
++ ppType t1
597 _
-> error "Type error in monadic op"
601 -> "mkDyadic " ++ sl_name i
++ ppType t1
602 _
-> error "Type error in dyadic op"
604 -> let (argTys
, resTy
) = flatTys
(ty i
)
605 tvs
= nub (tvsIn
(ty i
))
607 "mkGenPrimOp " ++ sl_name i
++ " "
608 ++ listify
(map ppTyVar tvs
) ++ " "
609 ++ listify
(map ppType argTys
) ++ " "
610 ++ "(" ++ ppType resTy
++ ")"
612 sl_name
:: Entry
-> String
613 sl_name i
= "(fsLit \"" ++ name i
++ "\") "
615 ppTyVar
:: String -> String
616 ppTyVar
"a" = "alphaTyVar"
617 ppTyVar
"b" = "betaTyVar"
618 ppTyVar
"c" = "gammaTyVar"
619 ppTyVar
"s" = "deltaTyVar"
620 ppTyVar
"o" = "openAlphaTyVar"
621 ppTyVar _
= error "Unknown type var"
623 ppType
:: Ty
-> String
624 ppType
(TyApp
"Any" []) = "anyTy"
625 ppType
(TyApp
"Bool" []) = "boolTy"
627 ppType
(TyApp
"Int#" []) = "intPrimTy"
628 ppType
(TyApp
"Int32#" []) = "int32PrimTy"
629 ppType
(TyApp
"Int64#" []) = "int64PrimTy"
630 ppType
(TyApp
"Char#" []) = "charPrimTy"
631 ppType
(TyApp
"Word#" []) = "wordPrimTy"
632 ppType
(TyApp
"Word32#" []) = "word32PrimTy"
633 ppType
(TyApp
"Word64#" []) = "word64PrimTy"
634 ppType
(TyApp
"Addr#" []) = "addrPrimTy"
635 ppType
(TyApp
"Float#" []) = "floatPrimTy"
636 ppType
(TyApp
"Double#" []) = "doublePrimTy"
637 ppType
(TyApp
"ByteArray#" []) = "byteArrayPrimTy"
638 ppType
(TyApp
"RealWorld" []) = "realWorldTy"
639 ppType
(TyApp
"ThreadId#" []) = "threadIdPrimTy"
640 ppType
(TyApp
"ForeignObj#" []) = "foreignObjPrimTy"
641 ppType
(TyApp
"BCO#" []) = "bcoPrimTy"
642 ppType
(TyApp
"()" []) = "unitTy" -- unitTy is TysWiredIn's name for ()
644 ppType
(TyVar
"a") = "alphaTy"
645 ppType
(TyVar
"b") = "betaTy"
646 ppType
(TyVar
"c") = "gammaTy"
647 ppType
(TyVar
"s") = "deltaTy"
648 ppType
(TyVar
"o") = "openAlphaTy"
650 ppType
(TyApp
"State#" [x
]) = "mkStatePrimTy " ++ ppType x
651 ppType
(TyApp
"MutVar#" [x
,y
]) = "mkMutVarPrimTy " ++ ppType x
653 ppType
(TyApp
"MutableArray#" [x
,y
]) = "mkMutableArrayPrimTy " ++ ppType x
655 ppType
(TyApp
"MutableArrayArray#" [x
]) = "mkMutableArrayArrayPrimTy " ++ ppType x
656 ppType
(TyApp
"MutableByteArray#" [x
]) = "mkMutableByteArrayPrimTy "
658 ppType
(TyApp
"Array#" [x
]) = "mkArrayPrimTy " ++ ppType x
659 ppType
(TyApp
"ArrayArray#" []) = "mkArrayArrayPrimTy"
662 ppType
(TyApp
"Weak#" [x
]) = "mkWeakPrimTy " ++ ppType x
663 ppType
(TyApp
"StablePtr#" [x
]) = "mkStablePtrPrimTy " ++ ppType x
664 ppType
(TyApp
"StableName#" [x
]) = "mkStableNamePrimTy " ++ ppType x
666 ppType
(TyApp
"MVar#" [x
,y
]) = "mkMVarPrimTy " ++ ppType x
668 ppType
(TyApp
"TVar#" [x
,y
]) = "mkTVarPrimTy " ++ ppType x
670 ppType
(TyUTup ts
) = "(mkTupleTy UnboxedTuple "
671 ++ listify
(map ppType ts
) ++ ")"
673 ppType
(TyF s d
) = "(mkFunTy (" ++ ppType s
++ ") (" ++ ppType d
++ "))"
676 = error ("ppType: can't handle: " ++ show other
++ "\n")
678 listify
:: [String] -> String
679 listify ss
= "[" ++ concat (intersperse ", " ss
) ++ "]"
681 flatTys
:: Ty
-> ([Ty
],Ty
)
682 flatTys
(TyF t1 t2
) = case flatTys t2
of (ts
,t
) -> (t1
:ts
,t
)
683 flatTys other
= ([],other
)
685 tvsIn
:: Ty
-> [TyVar
]
686 tvsIn
(TyF t1 t2
) = tvsIn t1
++ tvsIn t2
687 tvsIn
(TyApp _ tys
) = concatMap tvsIn tys
688 tvsIn
(TyVar tv
) = [tv
]
689 tvsIn
(TyUTup tys
) = concatMap tvsIn tys
691 tyconsIn
:: Ty
-> [TyCon
]
692 tyconsIn
(TyF t1 t2
) = tyconsIn t1 `
union` tyconsIn t2
693 tyconsIn
(TyApp tc tys
) = foldr union [tc
] $ map tyconsIn tys
694 tyconsIn
(TyVar _
) = []
695 tyconsIn
(TyUTup tys
) = foldr union [] $ map tyconsIn tys
698 arity
= length . fst . flatTys