2 ------------------------------------------------------------------
3 -- A primop-table mangling program --
4 ------------------------------------------------------------------
14 import System
( getArgs )
15 import Maybe ( catMaybes )
18 main
= getArgs >>= \args
->
19 if length args
/= 1 ||
head args `
notElem` known_args
20 then error ("usage: genprimopcode command < primops.txt > ...\n"
21 ++ " where command is one of\n"
22 ++ unlines (map (" "++) known_args
)
27 Left err
-> error ("parse error at " ++ (show err
))
28 Right p_o_specs
@(Info _ entries
)
29 -> seq (sanityTop p_o_specs
) (
33 -> putStr (gen_data_decl p_o_specs
)
36 -> putStr (gen_switch_from_attribs
38 "primOpHasSideEffects" p_o_specs
)
41 -> putStr (gen_switch_from_attribs
43 "primOpOutOfLine" p_o_specs
)
46 -> putStr (gen_switch_from_attribs
48 "commutableOp" p_o_specs
)
51 -> putStr (gen_switch_from_attribs
53 "primOpNeedsWrapper" p_o_specs
)
56 -> putStr (gen_switch_from_attribs
58 "primOpCanFail" p_o_specs
)
61 -> putStr (gen_switch_from_attribs
63 "primOpStrictness" p_o_specs
)
65 "--primop-primop-info"
66 -> putStr (gen_primop_info p_o_specs
)
69 -> putStr (gen_primop_tag p_o_specs
)
72 -> putStr (gen_primop_list p_o_specs
)
74 "--make-haskell-wrappers"
75 -> putStr (gen_wrappers p_o_specs
)
77 "--make-haskell-source"
78 -> putStr (gen_hs_source p_o_specs
)
80 "--make-ext-core-source"
81 -> putStr (gen_ext_core_source entries
)
84 -> putStr (gen_latex_doc p_o_specs
)
86 _
-> error "Should not happen, known_args out of sync?"
89 known_args
:: [String]
98 "--primop-primop-info",
101 "--make-haskell-wrappers",
102 "--make-haskell-source",
103 "--make-ext-core-source",
107 ------------------------------------------------------------------
108 -- Code generators -----------------------------------------------
109 ------------------------------------------------------------------
111 gen_hs_source
:: Info
-> String
112 gen_hs_source
(Info defaults entries
) =
113 "-----------------------------------------------------------------------------\n"
115 ++ "-- Module : GHC.Prim\n"
117 ++ "-- Maintainer : cvs-ghc@haskell.org\n"
118 ++ "-- Stability : internal\n"
119 ++ "-- Portability : non-portable (GHC extensions)\n"
121 ++ "-- GHC\'s primitive types and operations.\n"
123 ++ "-----------------------------------------------------------------------------\n"
124 ++ "module GHC.Prim (\n"
125 ++ unlines (map (("\t" ++) . hdr
) entries
)
129 ++ "This is a generated file (generated by genprimopcode).\n"
130 ++ "It is not code to actually be used. Its only purpose is to be\n"
131 ++ "consumed by haddock.\n"
134 ++ "import GHC.Bool\n"
137 ++ unlines (map opt defaults
)
139 ++ unlines (concatMap ent entries
) ++ "\n\n\n"
140 where opt
(OptionFalse n
) = n
++ " = False"
141 opt
(OptionTrue n
) = n
++ " = True"
142 opt
(OptionString n v
) = n
++ " = { " ++ v
++ "}"
144 hdr s
@(Section
{}) = sec s
145 hdr
(PrimOpSpec
{ name
= n
}) = wrapOp n
++ ","
146 hdr
(PseudoOpSpec
{ name
= n
}) = wrapOp n
++ ","
147 hdr
(PrimTypeSpec
{ ty
= TyApp n _
}) = wrapTy n
++ ","
148 hdr
(PrimTypeSpec
{}) = error "Illegal type spec"
150 ent
(Section
{}) = []
151 ent o
@(PrimOpSpec
{}) = spec o
152 ent o
@(PrimTypeSpec
{}) = spec o
153 ent o
@(PseudoOpSpec
{}) = spec o
155 sec s
= "\n-- * " ++ escape
(title s
) ++ "\n"
156 ++ (unlines $ map ("-- " ++ ) $ lines $ unlatex
$ escape
$ "|" ++ desc s
) ++ "\n"
158 spec o
= comm
: decls
159 where decls
= case o
of
160 PrimOpSpec
{ name
= n
, ty
= t
} ->
161 [ wrapOp n
++ " :: " ++ pprTy t
,
162 wrapOp n
++ " = let x = x in x" ]
163 PseudoOpSpec
{ name
= n
, ty
= t
} ->
164 [ wrapOp n
++ " :: " ++ pprTy t
,
165 wrapOp n
++ " = let x = x in x" ]
166 PrimTypeSpec
{ ty
= t
} ->
167 [ "data " ++ pprTy t
]
170 comm
= case (desc o
) of
172 d
-> "\n" ++ (unlines $ map ("-- " ++ ) $ lines $ unlatex
$ escape
$ "|" ++ d
)
174 wrapOp nm |
isAlpha (head nm
) = nm
175 |
otherwise = "(" ++ nm
++ ")"
176 wrapTy nm |
isAlpha (head nm
) = nm
177 |
otherwise = "(" ++ nm
++ ")"
178 unlatex s
= case s
of
179 '\\':'t
':'e
':'x
':'t
':'t
':'t
':'{':cs
-> markup
"@" "@" cs
180 '{':'\\':'t
':'t
':cs
-> markup
"@" "@" cs
181 '{':'\\':'i
':'t
':cs
-> markup
"/" "/" cs
182 c
: cs
-> c
: unlatex cs
184 markup s t xs
= s
++ mk
(dropWhile isSpace xs
)
186 mk
('\n':cs
) = ' ' : mk cs
187 mk
('}':cs
) = t
++ unlatex cs
188 mk
(c
:cs
) = c
: mk cs
189 escape
= concatMap (\c
-> if c `
elem` special
then '\\':c
:[] else c
:[])
190 where special
= "/'`\"@<"
194 pty
(TyF t1 t2
) = pbty t1
++ " -> " ++ pty t2
196 pbty
(TyApp tc ts
) = tc
++ concat (map (' ' :) (map paty ts
))
197 pbty
(TyUTup ts
) = "(# "
198 ++ concat (intersperse "," (map pty ts
))
203 paty t
= "(" ++ pty t
++ ")"
205 -- Generates the type environment that the stand-alone External Core tools use.
206 gen_ext_core_source
:: [Entry
] -> String
207 gen_ext_core_source entries
=
208 "-----------------------------------------------------------------------\n"
209 ++ "-- This module is automatically generated by the GHC utility\n"
210 ++ "-- \"genprimopcode\". Do not edit!\n"
211 ++ "-----------------------------------------------------------------------\n"
212 ++ "module Language.Core.PrimEnv(primTcs, primVals, intLitTypes, ratLitTypes,"
213 ++ "\n charLitTypes, stringLitTypes) where\nimport Language.Core.Core"
214 ++ "\nimport Language.Core.Encoding\n\n"
215 ++ "primTcs :: [(Tcon, Kind)]\n"
217 ++ printList tcEnt entries
219 ++ "primVals :: [(Var, Ty)]\n"
221 ++ printList valEnt entries
223 ++ "intLitTypes :: [Ty]\n"
224 ++ "intLitTypes = [\n"
225 ++ printList tyEnt
(intLitTys entries
)
227 ++ "ratLitTypes :: [Ty]\n"
228 ++ "ratLitTypes = [\n"
229 ++ printList tyEnt
(ratLitTys entries
)
231 ++ "charLitTypes :: [Ty]\n"
232 ++ "charLitTypes = [\n"
233 ++ printList tyEnt
(charLitTys entries
)
235 ++ "stringLitTypes :: [Ty]\n"
236 ++ "stringLitTypes = [\n"
237 ++ printList tyEnt
(stringLitTys entries
)
240 where printList f
= concat . intersperse ",\n" . filter (not . null) . map f
241 tcEnt
(PrimTypeSpec
{ty
=t
}) =
243 TyApp tc args
-> parens tc
(tcKind tc args
)
244 _
-> error ("tcEnt: type in PrimTypeSpec is not a type"
245 ++ " constructor: " ++ show t
)
248 -- The primops.txt.pp format doesn't have enough information in it to
249 -- print out some of the information that ext-core needs (like kinds,
250 -- and later on in this code, module names) so we special-case. An
251 -- alternative would be to refer to things indirectly and hard-wire
252 -- certain things (e.g., the kind of the Any constructor, here) into
253 -- ext-core's Prims module again.
254 tcKind
"Any" _
= "Klifted"
255 tcKind tc
[] |
last tc
== '#' = "Kunlifted"
256 tcKind tc
[] |
otherwise = "Klifted"
257 -- assumes that all type arguments are lifted (are they?)
258 tcKind tc
(v
:as) = "(Karrow Klifted " ++ tcKind tc
as
260 valEnt
(PseudoOpSpec
{name
=n
, ty
=t
}) = valEntry n t
261 valEnt
(PrimOpSpec
{name
=n
, ty
=t
}) = valEntry n t
263 valEntry name ty
= parens name
(mkForallTy
(freeTvars ty
) (pty ty
))
264 where pty
(TyF t1 t2
) = mkFunTy
(pty t1
) (pty t2
)
265 pty
(TyApp tc ts
) = mkTconApp
(mkTcon tc
) (map pty ts
)
266 pty
(TyUTup ts
) = mkUtupleTy
(map pty ts
)
267 pty
(TyVar tv
) = paren
$ "Tvar \"" ++ tv
++ "\""
269 mkFunTy s1 s2
= "Tapp " ++ (paren
("Tapp (Tcon tcArrow)"
272 mkTconApp tc args
= foldl tapp tc args
273 mkTcon tc
= paren
$ "Tcon " ++ paren
(qualify
True tc
)
274 mkUtupleTy args
= foldl tapp
(tcUTuple
(length args
)) args
276 mkForallTy vs t
= foldr
277 (\ v s
-> "Tforall " ++
278 (paren
(quot v
++ ", " ++ vKind v
)) ++ " "
285 freeTvars
(TyF t1 t2
) = freeTvars t1 `
union` freeTvars t2
286 freeTvars
(TyApp _ tys
) = freeTvarss tys
287 freeTvars
(TyVar v
) = [v
]
288 freeTvars
(TyUTup tys
) = freeTvarss tys
289 freeTvarss
= nub . concatMap freeTvars
291 tapp s nextArg
= paren
$ "Tapp " ++ s
++ " " ++ paren nextArg
292 tcUTuple n
= paren
$ "Tcon " ++ paren
(qualify
False $ "Z"
295 tyEnt
(PrimTypeSpec
{ty
=(TyApp tc args
)}) = " " ++ paren
("Tcon " ++
296 (paren
(qualify
True tc
)))
299 -- more hacks. might be better to do this on the ext-core side,
300 -- as per earlier comment
301 qualify _ tc | tc
== "Bool" = "Just boolMname" ++ ", "
303 qualify _ tc | tc
== "()" = "Just baseMname" ++ ", "
305 qualify enc tc
= "Just primMname" ++ ", " ++ (ze enc tc
)
306 ze enc tc
= (if enc
then "zEncodeString " else "")
307 ++ "\"" ++ tc
++ "\""
309 intLitTys
= prefixes
["Int", "Word", "Addr", "Char"]
310 ratLitTys
= prefixes
["Float", "Double"]
311 charLitTys
= prefixes
["Char"]
312 stringLitTys
= prefixes
["Addr"]
313 prefixes ps
= filter (\ t
->
315 (PrimTypeSpec
{ty
=(TyApp tc args
)}) ->
316 any (\ p
-> p `
isPrefixOf` tc
) ps
319 parens n ty
= " (zEncodeString \"" ++ n
++ "\", " ++ ty
++ ")"
320 paren s
= "(" ++ s
++ ")"
321 quot s
= "\"" ++ s
++ "\""
323 gen_latex_doc
:: Info
-> String
324 gen_latex_doc
(Info defaults entries
)
325 = "\\primopdefaults{"
326 ++ mk_options defaults
328 ++ (concat (map mk_entry entries
))
329 where mk_entry
(PrimOpSpec
{cons
=constr
,name
=n
,ty
=t
,cat
=c
,desc
=d
,opts
=o
}) =
331 ++ latex_encode constr
++ "}{"
332 ++ latex_encode n
++ "}{"
333 ++ latex_encode
(zencode n
) ++ "}{"
334 ++ latex_encode
(show c
) ++ "}{"
335 ++ latex_encode
(mk_source_ty t
) ++ "}{"
336 ++ latex_encode
(mk_core_ty t
) ++ "}{"
340 mk_entry
(Section
{title
=ti
,desc
=d
}) =
342 ++ latex_encode ti
++ "}{"
344 mk_entry
(PrimTypeSpec
{ty
=t
,desc
=d
,opts
=o
}) =
346 ++ latex_encode
(mk_source_ty t
) ++ "}{"
347 ++ latex_encode
(mk_core_ty t
) ++ "}{"
351 mk_entry
(PseudoOpSpec
{name
=n
,ty
=t
,desc
=d
,opts
=o
}) =
353 ++ latex_encode
(zencode n
) ++ "}{"
354 ++ latex_encode
(mk_source_ty t
) ++ "}{"
355 ++ latex_encode
(mk_core_ty t
) ++ "}{"
359 mk_source_ty typ
= pty typ
360 where pty
(TyF t1 t2
) = pbty t1
++ " -> " ++ pty t2
362 pbty
(TyApp tc ts
) = tc
++ (concat (map (' ':) (map paty ts
)))
363 pbty
(TyUTup ts
) = "(# " ++ (concat (intersperse "," (map pty ts
))) ++ " #)"
366 paty t
= "(" ++ pty t
++ ")"
368 mk_core_ty typ
= foralls
++ (pty typ
)
369 where pty
(TyF t1 t2
) = pbty t1
++ " -> " ++ pty t2
371 pbty
(TyApp tc ts
) = (zencode tc
) ++ (concat (map (' ':) (map paty ts
)))
372 pbty
(TyUTup ts
) = (zencode
(utuplenm
(length ts
))) ++ (concat ((map (' ':) (map paty ts
))))
374 paty
(TyVar tv
) = zencode tv
375 paty
(TyApp tc
[]) = zencode tc
376 paty t
= "(" ++ pty t
++ ")"
378 utuplenm n
= "(#" ++ (replicate (n
-1) ',') ++ "#)"
379 foralls
= if tvars
== [] then "" else "%forall " ++ (tbinds tvars
)
382 tbinds
("o":tbs
) = "(o::?) " ++ (tbinds tbs
)
383 tbinds
(tv
:tbs
) = tv
++ " " ++ (tbinds tbs
)
384 tvars_of
(TyF t1 t2
) = tvars_of t1 `
union` tvars_of t2
385 tvars_of
(TyApp _ ts
) = foldl union [] (map tvars_of ts
)
386 tvars_of
(TyUTup ts
) = foldr union [] (map tvars_of ts
)
387 tvars_of
(TyVar tv
) = [tv
]
391 ++ mk_has_side_effects o
++ "}{"
392 ++ mk_out_of_line o
++ "}{"
393 ++ mk_commutable o
++ "}{"
394 ++ mk_needs_wrapper o
++ "}{"
395 ++ mk_can_fail o
++ "}{"
396 ++ latex_encode
(mk_strictness o
) ++ "}{"
399 mk_has_side_effects o
= mk_bool_opt o
"has_side_effects" "Has side effects." "Has no side effects."
400 mk_out_of_line o
= mk_bool_opt o
"out_of_line" "Implemented out of line." "Implemented in line."
401 mk_commutable o
= mk_bool_opt o
"commutable" "Commutable." "Not commutable."
402 mk_needs_wrapper o
= mk_bool_opt o
"needs_wrapper" "Needs wrapper." "Needs no wrapper."
403 mk_can_fail o
= mk_bool_opt o
"can_fail" "Can fail." "Cannot fail."
405 mk_bool_opt o opt_name if_true if_false
=
406 case lookup_attrib opt_name o
of
407 Just
(OptionTrue _
) -> if_true
408 Just
(OptionFalse _
) -> if_false
409 Just
(OptionString _ _
) -> error "String value for boolean option"
413 case lookup_attrib
"strictness" o
of
414 Just
(OptionString _ s
) -> s
-- for now
415 Just _
-> error "Boolean value for strictness"
419 case maybe_tuple xs
of
420 Just n
-> n
-- Tuples go to Z2T etc
421 Nothing
-> concat (map encode_ch xs
)
423 maybe_tuple
"(# #)" = Just
("Z1H")
424 maybe_tuple
('(' : '#' : cs
) = case count_commas
(0::Int) cs
of
425 (n
, '#' : ')' : _
) -> Just
('Z
' : shows (n
+1) "H")
427 maybe_tuple
"()" = Just
("Z0T")
428 maybe_tuple
('(' : cs
) = case count_commas
(0::Int) cs
of
429 (n
, ')' : _
) -> Just
('Z
' : shows (n
+1) "T")
431 maybe_tuple _
= Nothing
433 count_commas
:: Int -> String -> (Int, String)
434 count_commas n
(',' : cs
) = count_commas
(n
+1) cs
435 count_commas n cs
= (n
,cs
)
437 unencodedChar
:: Char -> Bool -- True for chars that don't need encoding
438 unencodedChar
'Z
' = False
439 unencodedChar
'z
' = False
440 unencodedChar c
= isAlphaNum c
442 encode_ch
:: Char -> String
443 encode_ch c | unencodedChar c
= [c
] -- Common case first
446 encode_ch
'(' = "ZL" -- Needed for things like (,), and (->)
447 encode_ch
')' = "ZR" -- For symmetry with (
467 encode_ch
'\'' = "zq"
468 encode_ch
'\\' = "zr"
473 encode_ch c
= 'z
' : shows (ord c
) "U"
476 latex_encode
(c
:cs
) | c `
elem`
"#$%&_^{}" = "\\" ++ c
:(latex_encode cs
)
477 latex_encode
('~
':cs
) = "\\verb!~!" ++ (latex_encode cs
)
478 latex_encode
('\\':cs
) = "$\\backslash$" ++ (latex_encode cs
)
479 latex_encode
(c
:cs
) = c
:(latex_encode cs
)
481 gen_wrappers
:: Info
-> String
482 gen_wrappers
(Info _ entries
)
483 = "{-# LANGUAGE NoImplicitPrelude, UnboxedTuples #-}\n"
484 -- Dependencies on Prelude must be explicit in libraries/base, but we
485 -- don't need the Prelude here so we add NoImplicitPrelude.
486 ++ "module GHC.PrimopWrappers where\n"
487 ++ "import qualified GHC.Prim\n"
488 ++ "import GHC.Bool (Bool)\n"
489 ++ "import GHC.Unit ()\n"
490 ++ "import GHC.Prim (" ++ types
++ ")\n"
491 ++ unlines (concatMap f specs
)
493 specs
= filter (not.dodgy
) (filter is_primop entries
)
494 tycons
= foldr union [] $ map (tyconsIn
. ty
) specs
495 tycons
' = filter (`
notElem`
["()", "Bool"]) tycons
496 types
= concat $ intersperse ", " tycons
'
497 f spec
= let args
= map (\n -> "a" ++ show n
) [1 .. arity
(ty spec
)]
498 src_name
= wrap
(name spec
)
499 lhs
= src_name
++ " " ++ unwords args
500 rhs
= "(GHC.Prim." ++ name spec
++ ") " ++ unwords args
501 in ["{-# NOINLINE " ++ src_name
++ " #-}",
502 src_name
++ " :: " ++ pprTy
(ty spec
),
504 wrap nm |
isLower (head nm
) = nm
505 |
otherwise = "(" ++ nm
++ ")"
509 [-- C code generator can't handle these
512 -- not interested in parallel support
513 "par#", "parGlobal#", "parLocal#", "parAt#",
514 "parAtAbs#", "parAtRel#", "parAtForNow#"
517 gen_primop_list
:: Info
-> String
518 gen_primop_list
(Info _ entries
)
520 [ " [" ++ cons first
]
522 map (\p
-> " , " ++ cons p
) rest
525 ) where (first
:rest
) = filter is_primop entries
527 gen_primop_tag
:: Info
-> String
528 gen_primop_tag
(Info _ entries
)
529 = unlines (max_def_type
: max_def
:
530 tagOf_type
: zipWith f primop_entries
[1 :: Int ..])
532 primop_entries
= filter is_primop entries
533 tagOf_type
= "tagOf_PrimOp :: PrimOp -> FastInt"
534 f i n
= "tagOf_PrimOp " ++ cons i
++ " = _ILIT(" ++ show n
++ ")"
535 max_def_type
= "maxPrimOpTag :: Int"
536 max_def
= "maxPrimOpTag = " ++ show (length primop_entries
)
538 gen_data_decl
:: Info
-> String
539 gen_data_decl
(Info _ entries
)
540 = let conss
= map cons
(filter is_primop entries
)
541 in "data PrimOp\n = " ++ head conss
++ "\n"
542 ++ unlines (map (" | "++) (tail conss
))
544 gen_switch_from_attribs
:: String -> String -> Info
-> String
545 gen_switch_from_attribs attrib_name fn_name
(Info defaults entries
)
546 = let defv
= lookup_attrib attrib_name defaults
547 alternatives
= catMaybes (map mkAlt
(filter is_primop entries
))
549 getAltRhs
(OptionFalse _
) = "False"
550 getAltRhs
(OptionTrue _
) = "True"
551 getAltRhs
(OptionString _ s
) = s
554 = case lookup_attrib attrib_name
(opts po
) of
556 Just xx
-> Just
(fn_name
++ " " ++ cons po
++ " = " ++ getAltRhs xx
)
560 Nothing
-> error ("gen_switch_from: " ++ attrib_name
)
562 -> unlines alternatives
563 ++ fn_name
++ " _ = " ++ getAltRhs xx
++ "\n"
565 ------------------------------------------------------------------
566 -- Create PrimOpInfo text from PrimOpSpecs -----------------------
567 ------------------------------------------------------------------
569 gen_primop_info
:: Info
-> String
570 gen_primop_info
(Info _ entries
)
571 = unlines (map mkPOItext
(filter is_primop entries
))
573 mkPOItext
:: Entry
-> String
574 mkPOItext i
= mkPOI_LHS_text i
++ mkPOI_RHS_text i
576 mkPOI_LHS_text
:: Entry
-> String
578 = "primOpInfo " ++ cons i
++ " = "
580 mkPOI_RHS_text
:: Entry
-> String
586 -> "mkCompare " ++ sl_name i
++ ppType t1
587 _
-> error "Type error in comparison op"
591 -> "mkMonadic " ++ sl_name i
++ ppType t1
592 _
-> error "Type error in monadic op"
596 -> "mkDyadic " ++ sl_name i
++ ppType t1
597 _
-> error "Type error in dyadic op"
599 -> let (argTys
, resTy
) = flatTys
(ty i
)
600 tvs
= nub (tvsIn
(ty i
))
602 "mkGenPrimOp " ++ sl_name i
++ " "
603 ++ listify
(map ppTyVar tvs
) ++ " "
604 ++ listify
(map ppType argTys
) ++ " "
605 ++ "(" ++ ppType resTy
++ ")"
607 sl_name
:: Entry
-> String
608 sl_name i
= "(fsLit \"" ++ name i
++ "\") "
610 ppTyVar
:: String -> String
611 ppTyVar
"a" = "alphaTyVar"
612 ppTyVar
"b" = "betaTyVar"
613 ppTyVar
"c" = "gammaTyVar"
614 ppTyVar
"s" = "deltaTyVar"
615 ppTyVar
"o" = "openAlphaTyVar"
616 ppTyVar _
= error "Unknown type var"
618 ppType
:: Ty
-> String
619 ppType
(TyApp
"Bool" []) = "boolTy"
621 ppType
(TyApp
"Int#" []) = "intPrimTy"
622 ppType
(TyApp
"Int32#" []) = "int32PrimTy"
623 ppType
(TyApp
"Int64#" []) = "int64PrimTy"
624 ppType
(TyApp
"Char#" []) = "charPrimTy"
625 ppType
(TyApp
"Word#" []) = "wordPrimTy"
626 ppType
(TyApp
"Word32#" []) = "word32PrimTy"
627 ppType
(TyApp
"Word64#" []) = "word64PrimTy"
628 ppType
(TyApp
"Addr#" []) = "addrPrimTy"
629 ppType
(TyApp
"Float#" []) = "floatPrimTy"
630 ppType
(TyApp
"Double#" []) = "doublePrimTy"
631 ppType
(TyApp
"ByteArray#" []) = "byteArrayPrimTy"
632 ppType
(TyApp
"RealWorld" []) = "realWorldTy"
633 ppType
(TyApp
"ThreadId#" []) = "threadIdPrimTy"
634 ppType
(TyApp
"ForeignObj#" []) = "foreignObjPrimTy"
635 ppType
(TyApp
"BCO#" []) = "bcoPrimTy"
636 ppType
(TyApp
"()" []) = "unitTy" -- unitTy is TysWiredIn's name for ()
638 ppType
(TyVar
"a") = "alphaTy"
639 ppType
(TyVar
"b") = "betaTy"
640 ppType
(TyVar
"c") = "gammaTy"
641 ppType
(TyVar
"s") = "deltaTy"
642 ppType
(TyVar
"o") = "openAlphaTy"
643 ppType
(TyApp
"State#" [x
]) = "mkStatePrimTy " ++ ppType x
644 ppType
(TyApp
"MutVar#" [x
,y
]) = "mkMutVarPrimTy " ++ ppType x
646 ppType
(TyApp
"MutableArray#" [x
,y
]) = "mkMutableArrayPrimTy " ++ ppType x
649 ppType
(TyApp
"MutableByteArray#" [x
]) = "mkMutableByteArrayPrimTy "
652 ppType
(TyApp
"Array#" [x
]) = "mkArrayPrimTy " ++ ppType x
655 ppType
(TyApp
"Weak#" [x
]) = "mkWeakPrimTy " ++ ppType x
656 ppType
(TyApp
"StablePtr#" [x
]) = "mkStablePtrPrimTy " ++ ppType x
657 ppType
(TyApp
"StableName#" [x
]) = "mkStableNamePrimTy " ++ ppType x
659 ppType
(TyApp
"MVar#" [x
,y
]) = "mkMVarPrimTy " ++ ppType x
661 ppType
(TyApp
"TVar#" [x
,y
]) = "mkTVarPrimTy " ++ ppType x
663 ppType
(TyUTup ts
) = "(mkTupleTy Unboxed " ++ show (length ts
)
665 ++ listify
(map ppType ts
) ++ ")"
667 ppType
(TyF s d
) = "(mkFunTy (" ++ ppType s
++ ") (" ++ ppType d
++ "))"
670 = error ("ppType: can't handle: " ++ show other
++ "\n")
672 listify
:: [String] -> String
673 listify ss
= "[" ++ concat (intersperse ", " ss
) ++ "]"
675 flatTys
:: Ty
-> ([Ty
],Ty
)
676 flatTys
(TyF t1 t2
) = case flatTys t2
of (ts
,t
) -> (t1
:ts
,t
)
677 flatTys other
= ([],other
)
679 tvsIn
:: Ty
-> [TyVar
]
680 tvsIn
(TyF t1 t2
) = tvsIn t1
++ tvsIn t2
681 tvsIn
(TyApp _ tys
) = concatMap tvsIn tys
682 tvsIn
(TyVar tv
) = [tv
]
683 tvsIn
(TyUTup tys
) = concatMap tvsIn tys
685 tyconsIn
:: Ty
-> [TyCon
]
686 tyconsIn
(TyF t1 t2
) = tyconsIn t1 `
union` tyconsIn t2
687 tyconsIn
(TyApp tc tys
) = foldr union [tc
] $ map tyconsIn tys
688 tyconsIn
(TyVar _
) = []
689 tyconsIn
(TyUTup tys
) = foldr union [] $ map tyconsIn tys
692 arity
= length . fst . flatTys