2 ------------------------------------------------------------------
3 -- A primop-table mangling program --
4 ------------------------------------------------------------------
13 import Data
.Maybe ( catMaybes )
14 import System
.Environment
( getArgs )
16 vecOptions
:: Entry
-> [(String,String,Int)]
18 concat [vecs | OptionVector vecs
<- opts i
]
20 desugarVectorSpec
:: Entry
-> [Entry
]
21 desugarVectorSpec i
@(Section
{}) = [i
]
22 desugarVectorSpec i
= case vecOptions i
of
24 vos
-> map genVecEntry vos
26 genVecEntry
:: (String,String,Int) -> Entry
27 genVecEntry
(con
,repCon
,n
) =
30 PrimVecOpSpec
{ cons
= "(" ++ concat (intersperse " " [cons i
, vecCat
, show n
, vecWidth
]) ++ ")"
34 , elemrep
= con
++ "ElemRep"
35 , ty
= desugarTy
(ty i
)
41 PrimVecTypeSpec
{ ty
= desugarTy
(ty i
)
44 , elemrep
= con
++ "ElemRep"
49 error "vector options can only be given for primops and primtypes"
51 vecCons
= con
++"X"++show n
++"#"
53 vecWidth
= conWidth con
54 pfx
= lowerHead con
++"X"++show n
55 vecTyName
= pfx
++"PrimTy"
57 name
' | Just pre
<- splitSuffix
(name i
) "Array#" = pre
++vec
++"Array#"
58 | Just pre
<- splitSuffix
(name i
) "OffAddr#" = pre
++vec
++"OffAddr#"
59 | Just pre
<- splitSuffix
(name i
) "ArrayAs#" = pre
++con
++"ArrayAs"++vec
++"#"
60 | Just pre
<- splitSuffix
(name i
) "OffAddrAs#" = pre
++con
++"OffAddrAs"++vec
++"#"
61 |
otherwise = init (name i
)++vec
++"#"
63 vec
= con
++"X"++show n
65 splitSuffix
:: Eq a
=> [a
] -> [a
] -> Maybe [a
]
67 |
drop len s
== suf
= Just
(take len s
)
70 len
= length s
- length suf
72 lowerHead s
= toLower (head s
) : tail s
75 desugarTy
(TyF s d
) = TyF
(desugarTy s
) (desugarTy d
)
76 desugarTy
(TyC s d
) = TyC
(desugarTy s
) (desugarTy d
)
77 desugarTy
(TyApp SCALAR
[]) = TyApp
(TyCon repCon
) []
78 desugarTy
(TyApp VECTOR
[]) = TyApp
(VecTyCon vecCons vecTyName
) []
79 desugarTy
(TyApp VECTUPLE
[]) = TyUTup
(replicate n
(TyApp
(TyCon repCon
) []))
80 desugarTy
(TyApp tycon ts
) = TyApp tycon
(map desugarTy ts
)
81 desugarTy t
@(TyVar
{}) = t
82 desugarTy
(TyUTup ts
) = TyUTup
(map desugarTy ts
)
84 conCat
:: String -> String
85 conCat
"Int8" = "IntVec"
86 conCat
"Int16" = "IntVec"
87 conCat
"Int32" = "IntVec"
88 conCat
"Int64" = "IntVec"
89 conCat
"Word8" = "WordVec"
90 conCat
"Word16" = "WordVec"
91 conCat
"Word32" = "WordVec"
92 conCat
"Word64" = "WordVec"
93 conCat
"Float" = "FloatVec"
94 conCat
"Double" = "FloatVec"
95 conCat con
= error $ "conCat: unknown type constructor " ++ con
++ "\n"
97 conWidth
:: String -> String
98 conWidth
"Int8" = "W8"
99 conWidth
"Int16" = "W16"
100 conWidth
"Int32" = "W32"
101 conWidth
"Int64" = "W64"
102 conWidth
"Word8" = "W8"
103 conWidth
"Word16" = "W16"
104 conWidth
"Word32" = "W32"
105 conWidth
"Word64" = "W64"
106 conWidth
"Float" = "W32"
107 conWidth
"Double" = "W64"
108 conWidth con
= error $ "conWidth: unknown type constructor " ++ con
++ "\n"
111 main
= getArgs >>= \args
->
112 if length args
/= 1 ||
head args `
notElem` known_args
113 then error ("usage: genprimopcode command < primops.txt > ...\n"
114 ++ " where command is one of\n"
115 ++ unlines (map (" "++) known_args
)
120 Left err
-> error ("parse error at " ++ (show err
))
121 Right p_o_specs
@(Info _ entries
)
122 -> seq (sanityTop p_o_specs
) (
126 -> putStr (gen_data_decl p_o_specs
)
129 -> putStr (gen_switch_from_attribs
131 "primOpHasSideEffects" p_o_specs
)
134 -> putStr (gen_switch_from_attribs
136 "primOpOutOfLine" p_o_specs
)
139 -> putStr (gen_switch_from_attribs
141 "commutableOp" p_o_specs
)
144 -> putStr (gen_switch_from_attribs
146 "primOpCodeSize" p_o_specs
)
149 -> putStr (gen_switch_from_attribs
151 "primOpCanFail" p_o_specs
)
154 -> putStr (gen_switch_from_attribs
156 "primOpStrictness" p_o_specs
)
159 -> putStr (gen_switch_from_attribs
161 "primOpFixity" p_o_specs
)
163 "--primop-primop-info"
164 -> putStr (gen_primop_info p_o_specs
)
167 -> putStr (gen_primop_tag p_o_specs
)
170 -> putStr (gen_primop_list p_o_specs
)
172 "--primop-vector-uniques"
173 -> putStr (gen_primop_vector_uniques p_o_specs
)
175 "--primop-vector-tys"
176 -> putStr (gen_primop_vector_tys p_o_specs
)
178 "--primop-vector-tys-exports"
179 -> putStr (gen_primop_vector_tys_exports p_o_specs
)
181 "--primop-vector-tycons"
182 -> putStr (gen_primop_vector_tycons p_o_specs
)
184 "--make-haskell-wrappers"
185 -> putStr (gen_wrappers p_o_specs
)
187 "--make-haskell-source"
188 -> putStr (gen_hs_source p_o_specs
)
190 "--make-ext-core-source"
191 -> putStr (gen_ext_core_source entries
)
194 -> putStr (gen_latex_doc p_o_specs
)
196 _
-> error "Should not happen, known_args out of sync?"
199 known_args
:: [String]
202 "--has-side-effects",
209 "--primop-primop-info",
212 "--primop-vector-uniques",
213 "--primop-vector-tys",
214 "--primop-vector-tys-exports",
215 "--primop-vector-tycons",
216 "--make-haskell-wrappers",
217 "--make-haskell-source",
218 "--make-ext-core-source",
222 ------------------------------------------------------------------
223 -- Code generators -----------------------------------------------
224 ------------------------------------------------------------------
226 gen_hs_source
:: Info
-> String
227 gen_hs_source
(Info defaults entries
) =
229 ++ "This is a generated file (generated by genprimopcode).\n"
230 ++ "It is not code to actually be used. Its only purpose is to be\n"
231 ++ "consumed by haddock.\n"
234 ++ "-----------------------------------------------------------------------------\n"
236 ++ "-- Module : GHC.Prim\n"
238 ++ "-- Maintainer : ghc-devs@haskell.org\n"
239 ++ "-- Stability : internal\n"
240 ++ "-- Portability : non-portable (GHC extensions)\n"
242 ++ "-- GHC\'s primitive types and operations.\n"
243 ++ "-- Use GHC.Exts from the base package instead of importing this\n"
244 ++ "-- module directly.\n"
246 ++ "-----------------------------------------------------------------------------\n"
247 ++ "{-# LANGUAGE MagicHash, MultiParamTypeClasses, NoImplicitPrelude, UnboxedTuples #-}\n"
248 ++ "module GHC.Prim (\n"
249 ++ unlines (map (("\t" ++) . hdr
) entries
')
253 ++ unlines (map opt defaults
)
255 ++ unlines (concatMap ent entries
') ++ "\n\n\n"
256 where entries
' = concatMap desugarVectorSpec entries
258 opt
(OptionFalse n
) = n
++ " = False"
259 opt
(OptionTrue n
) = n
++ " = True"
260 opt
(OptionString n v
) = n
++ " = { " ++ v
++ "}"
261 opt
(OptionInteger n v
) = n
++ " = " ++ show v
262 opt
(OptionVector _
) = ""
263 opt
(OptionFixity mf
) = "fixity" ++ " = " ++ show mf
265 hdr s
@(Section
{}) = sec s
266 hdr
(PrimOpSpec
{ name
= n
}) = wrapOp n
++ ","
267 hdr
(PrimVecOpSpec
{ name
= n
}) = wrapOp n
++ ","
268 hdr
(PseudoOpSpec
{ name
= n
}) = wrapOp n
++ ","
269 hdr
(PrimTypeSpec
{ ty
= TyApp
(TyCon n
) _
}) = wrapTy n
++ ","
270 hdr
(PrimTypeSpec
{}) = error $ "Illegal type spec"
271 hdr
(PrimClassSpec
{ cls
= TyApp
(TyCon n
) _
}) = wrapTy n
++ ","
272 hdr
(PrimClassSpec
{}) = error "Illegal class spec"
273 hdr
(PrimVecTypeSpec
{ ty
= TyApp
(VecTyCon n _
) _
}) = wrapTy n
++ ","
274 hdr
(PrimVecTypeSpec
{}) = error $ "Illegal type spec"
276 ent
(Section
{}) = []
277 ent o
@(PrimOpSpec
{}) = spec o
278 ent o
@(PrimVecOpSpec
{}) = spec o
279 ent o
@(PrimTypeSpec
{}) = spec o
280 ent o
@(PrimClassSpec
{}) = spec o
281 ent o
@(PrimVecTypeSpec
{}) = spec o
282 ent o
@(PseudoOpSpec
{}) = spec o
284 sec s
= "\n-- * " ++ escape
(title s
) ++ "\n"
285 ++ (unlines $ map ("-- " ++ ) $ lines $ unlatex
$ escape
$ "|" ++ desc s
) ++ "\n"
287 spec o
= comm
: decls
288 where decls
= case o
of
289 PrimOpSpec
{ name
= n
, ty
= t
, opts
= options
} ->
290 [ pprFixity fixity n | OptionFixity
(Just fixity
) <- options
]
292 [ wrapOp n
++ " :: " ++ pprTy t
,
293 wrapOp n
++ " = let x = x in x" ]
294 PrimVecOpSpec
{ name
= n
, ty
= t
, opts
= options
} ->
295 [ pprFixity fixity n | OptionFixity
(Just fixity
) <- options
]
297 [ wrapOp n
++ " :: " ++ pprTy t
,
298 wrapOp n
++ " = let x = x in x" ]
299 PseudoOpSpec
{ name
= n
, ty
= t
} ->
300 [ wrapOp n
++ " :: " ++ pprTy t
,
301 wrapOp n
++ " = let x = x in x" ]
302 PrimTypeSpec
{ ty
= t
} ->
303 [ "data " ++ pprTy t
]
304 PrimClassSpec
{ cls
= t
} ->
305 [ "class " ++ pprTy t
]
306 PrimVecTypeSpec
{ ty
= t
} ->
307 [ "data " ++ pprTy t
]
310 comm
= case (desc o
) of
312 d
-> "\n" ++ (unlines $ map ("-- " ++ ) $ lines $ unlatex
$ escape
$ "|" ++ d
)
314 wrapOp nm |
isAlpha (head nm
) = nm
315 |
otherwise = "(" ++ nm
++ ")"
316 wrapTy nm |
isAlpha (head nm
) = nm
317 |
otherwise = "(" ++ nm
++ ")"
318 unlatex s
= case s
of
319 '\\':'t
':'e
':'x
':'t
':'t
':'t
':'{':cs
-> markup
"@" "@" cs
320 '{':'\\':'t
':'t
':cs
-> markup
"@" "@" cs
321 '{':'\\':'i
':'t
':cs
-> markup
"/" "/" cs
322 c
: cs
-> c
: unlatex cs
324 markup s t xs
= s
++ mk
(dropWhile isSpace xs
)
326 mk
('\n':cs
) = ' ' : mk cs
327 mk
('}':cs
) = t
++ unlatex cs
328 mk
(c
:cs
) = c
: mk cs
329 escape
= concatMap (\c
-> if c `
elem` special
then '\\':c
:[] else c
:[])
330 where special
= "/'`\"@<"
332 pprFixity
(Fixity i d
) n
= pprFixityDir d
++ " " ++ show i
++ " " ++ n
334 pprTy
:: Ty
-> String
337 pty
(TyF t1 t2
) = pbty t1
++ " -> " ++ pty t2
338 pty
(TyC t1 t2
) = pbty t1
++ " => " ++ pty t2
340 pbty
(TyApp tc ts
) = show tc
++ concat (map (' ' :) (map paty ts
))
341 pbty
(TyUTup ts
) = "(# "
342 ++ concat (intersperse "," (map pty ts
))
347 paty t
= "(" ++ pty t
++ ")"
349 -- Generates the type environment that the stand-alone External Core tools use.
350 gen_ext_core_source
:: [Entry
] -> String
351 gen_ext_core_source entries
=
352 "-----------------------------------------------------------------------\n"
353 ++ "-- This module is automatically generated by the GHC utility\n"
354 ++ "-- \"genprimopcode\". Do not edit!\n"
355 ++ "-----------------------------------------------------------------------\n"
356 ++ "module Language.Core.PrimEnv(primTcs, primVals, intLitTypes, ratLitTypes,"
357 ++ "\n charLitTypes, stringLitTypes) where\nimport Language.Core.Core"
358 ++ "\nimport Language.Core.Encoding\n\n"
359 ++ "primTcs :: [(Tcon, Kind)]\n"
361 ++ printList tcEnt entries
363 ++ "primVals :: [(Var, Ty)]\n"
365 ++ printList valEnt entries
367 ++ "intLitTypes :: [Ty]\n"
368 ++ "intLitTypes = [\n"
369 ++ printList tyEnt
(intLitTys entries
)
371 ++ "ratLitTypes :: [Ty]\n"
372 ++ "ratLitTypes = [\n"
373 ++ printList tyEnt
(ratLitTys entries
)
375 ++ "charLitTypes :: [Ty]\n"
376 ++ "charLitTypes = [\n"
377 ++ printList tyEnt
(charLitTys entries
)
379 ++ "stringLitTypes :: [Ty]\n"
380 ++ "stringLitTypes = [\n"
381 ++ printList tyEnt
(stringLitTys entries
)
384 where printList f
= concat . intersperse ",\n" . filter (not . null) . map f
385 tcEnt
(PrimTypeSpec
{ty
=t
}) =
387 TyApp tc args
-> parens
(show tc
) (tcKind tc args
)
388 _
-> error ("tcEnt: type in PrimTypeSpec is not a type"
389 ++ " constructor: " ++ show t
)
392 -- The primops.txt.pp format doesn't have enough information in it to
393 -- print out some of the information that ext-core needs (like kinds,
394 -- and later on in this code, module names) so we special-case. An
395 -- alternative would be to refer to things indirectly and hard-wire
396 -- certain things (e.g., the kind of the Any constructor, here) into
397 -- ext-core's Prims module again.
398 tcKind
(TyCon
"Any") _
= "Klifted"
399 tcKind tc
[] |
last (show tc
) == '#' = "Kunlifted"
400 tcKind _
[] |
otherwise = "Klifted"
401 -- assumes that all type arguments are lifted (are they?)
402 tcKind tc
(_v
:as) = "(Karrow Klifted " ++ tcKind tc
as
404 valEnt
(PseudoOpSpec
{name
=n
, ty
=t
}) = valEntry n t
405 valEnt
(PrimOpSpec
{name
=n
, ty
=t
}) = valEntry n t
407 valEntry name
' ty
' = parens name
' (mkForallTy
(freeTvars ty
') (pty ty
'))
408 where pty
(TyF t1 t2
) = mkFunTy
(pty t1
) (pty t2
)
409 pty
(TyC t1 t2
) = mkFunTy
(pty t1
) (pty t2
)
410 pty
(TyApp tc ts
) = mkTconApp
(mkTcon tc
) (map pty ts
)
411 pty
(TyUTup ts
) = mkUtupleTy
(map pty ts
)
412 pty
(TyVar tv
) = paren
$ "Tvar \"" ++ tv
++ "\""
414 mkFunTy s1 s2
= "Tapp " ++ (paren
("Tapp (Tcon tcArrow)"
417 mkTconApp tc args
= foldl tapp tc args
418 mkTcon tc
= paren
$ "Tcon " ++ paren
(qualify
True (show tc
))
419 mkUtupleTy args
= foldl tapp
(tcUTuple
(length args
)) args
421 mkForallTy vs t
= foldr
422 (\ v s
-> "Tforall " ++
423 (paren
(quote v
++ ", " ++ vKind v
)) ++ " "
430 freeTvars
(TyF t1 t2
) = freeTvars t1 `
union` freeTvars t2
431 freeTvars
(TyC t1 t2
) = freeTvars t1 `
union` freeTvars t2
432 freeTvars
(TyApp _ tys
) = freeTvarss tys
433 freeTvars
(TyVar v
) = [v
]
434 freeTvars
(TyUTup tys
) = freeTvarss tys
435 freeTvarss
= nub . concatMap freeTvars
437 tapp s nextArg
= paren
$ "Tapp " ++ s
++ " " ++ paren nextArg
438 tcUTuple n
= paren
$ "Tcon " ++ paren
(qualify
False $ "Z"
441 tyEnt
(PrimTypeSpec
{ty
=(TyApp tc _args
)}) = " " ++ paren
("Tcon " ++
442 (paren
(qualify
True (show tc
))))
445 -- more hacks. might be better to do this on the ext-core side,
446 -- as per earlier comment
447 qualify _ tc | tc
== "Bool" = "Just boolMname" ++ ", "
449 qualify _ tc | tc
== "()" = "Just baseMname" ++ ", "
451 qualify enc tc
= "Just primMname" ++ ", " ++ (ze enc tc
)
452 ze enc tc
= (if enc
then "zEncodeString " else "")
453 ++ "\"" ++ tc
++ "\""
455 intLitTys
= prefixes
["Int", "Word", "Addr", "Char"]
456 ratLitTys
= prefixes
["Float", "Double"]
457 charLitTys
= prefixes
["Char"]
458 stringLitTys
= prefixes
["Addr"]
459 prefixes ps
= filter (\ t
->
461 (PrimTypeSpec
{ty
=(TyApp tc _args
)}) ->
462 any (\ p
-> p `
isPrefixOf`
show tc
) ps
465 parens n ty
' = " (zEncodeString \"" ++ n
++ "\", " ++ ty
' ++ ")"
466 paren s
= "(" ++ s
++ ")"
467 quote s
= "\"" ++ s
++ "\""
469 gen_latex_doc
:: Info
-> String
470 gen_latex_doc
(Info defaults entries
)
471 = "\\primopdefaults{"
472 ++ mk_options defaults
474 ++ (concat (map mk_entry entries
))
475 where mk_entry
(PrimOpSpec
{cons
=constr
,name
=n
,ty
=t
,cat
=c
,desc
=d
,opts
=o
}) =
477 ++ latex_encode constr
++ "}{"
478 ++ latex_encode n
++ "}{"
479 ++ latex_encode
(zencode n
) ++ "}{"
480 ++ latex_encode
(show c
) ++ "}{"
481 ++ latex_encode
(mk_source_ty t
) ++ "}{"
482 ++ latex_encode
(mk_core_ty t
) ++ "}{"
486 mk_entry
(PrimVecOpSpec
{}) =
488 mk_entry
(Section
{title
=ti
,desc
=d
}) =
490 ++ latex_encode ti
++ "}{"
492 mk_entry
(PrimTypeSpec
{ty
=t
,desc
=d
,opts
=o
}) =
494 ++ latex_encode
(mk_source_ty t
) ++ "}{"
495 ++ latex_encode
(mk_core_ty t
) ++ "}{"
499 mk_entry
(PrimClassSpec
{cls
=t
,desc
=d
,opts
=o
}) =
501 ++ latex_encode
(mk_source_ty t
) ++ "}{"
502 ++ latex_encode
(mk_core_ty t
) ++ "}{"
506 mk_entry
(PrimVecTypeSpec
{}) =
508 mk_entry
(PseudoOpSpec
{name
=n
,ty
=t
,desc
=d
,opts
=o
}) =
510 ++ latex_encode
(zencode n
) ++ "}{"
511 ++ latex_encode
(mk_source_ty t
) ++ "}{"
512 ++ latex_encode
(mk_core_ty t
) ++ "}{"
516 mk_source_ty typ
= pty typ
517 where pty
(TyF t1 t2
) = pbty t1
++ " -> " ++ pty t2
518 pty
(TyC t1 t2
) = pbty t1
++ " => " ++ pty t2
520 pbty
(TyApp tc ts
) = show tc
++ (concat (map (' ':) (map paty ts
)))
521 pbty
(TyUTup ts
) = "(# " ++ (concat (intersperse "," (map pty ts
))) ++ " #)"
524 paty t
= "(" ++ pty t
++ ")"
526 mk_core_ty typ
= foralls
++ (pty typ
)
527 where pty
(TyF t1 t2
) = pbty t1
++ " -> " ++ pty t2
528 pty
(TyC t1 t2
) = pbty t1
++ " => " ++ pty t2
530 pbty
(TyApp tc ts
) = (zencode
(show tc
)) ++ (concat (map (' ':) (map paty ts
)))
531 pbty
(TyUTup ts
) = (zencode
(utuplenm
(length ts
))) ++ (concat ((map (' ':) (map paty ts
))))
533 paty
(TyVar tv
) = zencode tv
534 paty
(TyApp tc
[]) = zencode
(show tc
)
535 paty t
= "(" ++ pty t
++ ")"
537 utuplenm n
= "(#" ++ (replicate (n
-1) ',') ++ "#)"
538 foralls
= if tvars
== [] then "" else "%forall " ++ (tbinds tvars
)
541 tbinds
("o":tbs
) = "(o::?) " ++ (tbinds tbs
)
542 tbinds
(tv
:tbs
) = tv
++ " " ++ (tbinds tbs
)
543 tvars_of
(TyF t1 t2
) = tvars_of t1 `
union` tvars_of t2
544 tvars_of
(TyC t1 t2
) = tvars_of t1 `
union` tvars_of t2
545 tvars_of
(TyApp _ ts
) = foldl union [] (map tvars_of ts
)
546 tvars_of
(TyUTup ts
) = foldr union [] (map tvars_of ts
)
547 tvars_of
(TyVar tv
) = [tv
]
551 ++ mk_has_side_effects o
++ "}{"
552 ++ mk_out_of_line o
++ "}{"
553 ++ mk_commutable o
++ "}{"
554 ++ mk_needs_wrapper o
++ "}{"
555 ++ mk_can_fail o
++ "}{"
556 ++ mk_fixity o
++ "}{"
557 ++ latex_encode
(mk_strictness o
) ++ "}{"
560 mk_has_side_effects o
= mk_bool_opt o
"has_side_effects" "Has side effects." "Has no side effects."
561 mk_out_of_line o
= mk_bool_opt o
"out_of_line" "Implemented out of line." "Implemented in line."
562 mk_commutable o
= mk_bool_opt o
"commutable" "Commutable." "Not commutable."
563 mk_needs_wrapper o
= mk_bool_opt o
"needs_wrapper" "Needs wrapper." "Needs no wrapper."
564 mk_can_fail o
= mk_bool_opt o
"can_fail" "Can fail." "Cannot fail."
566 mk_bool_opt o opt_name if_true if_false
=
567 case lookup_attrib opt_name o
of
568 Just
(OptionTrue _
) -> if_true
569 Just
(OptionFalse _
) -> if_false
570 Just
(OptionString _ _
) -> error "String value for boolean option"
571 Just
(OptionInteger _ _
) -> error "Integer value for boolean option"
572 Just
(OptionFixity _
) -> error "Fixity value for boolean option"
573 Just
(OptionVector _
) -> error "vector template for boolean option"
577 case lookup_attrib
"strictness" o
of
578 Just
(OptionString _ s
) -> s
-- for now
579 Just _
-> error "Wrong value for strictness"
582 mk_fixity o
= case lookup_attrib
"fixity" o
of
583 Just
(OptionFixity
(Just
(Fixity i d
)))
584 -> pprFixityDir d
++ " " ++ show i
588 case maybe_tuple xs
of
589 Just n
-> n
-- Tuples go to Z2T etc
590 Nothing
-> concat (map encode_ch xs
)
592 maybe_tuple
"(# #)" = Just
("Z1H")
593 maybe_tuple
('(' : '#' : cs
) = case count_commas
(0::Int) cs
of
594 (n
, '#' : ')' : _
) -> Just
('Z
' : shows (n
+1) "H")
596 maybe_tuple
"()" = Just
("Z0T")
597 maybe_tuple
('(' : cs
) = case count_commas
(0::Int) cs
of
598 (n
, ')' : _
) -> Just
('Z
' : shows (n
+1) "T")
600 maybe_tuple _
= Nothing
602 count_commas
:: Int -> String -> (Int, String)
603 count_commas n
(',' : cs
) = count_commas
(n
+1) cs
604 count_commas n cs
= (n
,cs
)
606 unencodedChar
:: Char -> Bool -- True for chars that don't need encoding
607 unencodedChar
'Z
' = False
608 unencodedChar
'z
' = False
609 unencodedChar c
= isAlphaNum c
611 encode_ch
:: Char -> String
612 encode_ch c | unencodedChar c
= [c
] -- Common case first
615 encode_ch
'(' = "ZL" -- Needed for things like (,), and (->)
616 encode_ch
')' = "ZR" -- For symmetry with (
636 encode_ch
'\'' = "zq"
637 encode_ch
'\\' = "zr"
642 encode_ch c
= 'z
' : shows (ord c
) "U"
645 latex_encode
(c
:cs
) | c `
elem`
"#$%&_^{}" = "\\" ++ c
:(latex_encode cs
)
646 latex_encode
('~
':cs
) = "\\verb!~!" ++ (latex_encode cs
)
647 latex_encode
('\\':cs
) = "$\\backslash$" ++ (latex_encode cs
)
648 latex_encode
(c
:cs
) = c
:(latex_encode cs
)
650 gen_wrappers
:: Info
-> String
651 gen_wrappers
(Info _ entries
)
652 = "{-# LANGUAGE MagicHash, NoImplicitPrelude, UnboxedTuples #-}\n"
653 -- Dependencies on Prelude must be explicit in libraries/base, but we
654 -- don't need the Prelude here so we add NoImplicitPrelude.
655 ++ "module GHC.PrimopWrappers where\n"
656 ++ "import qualified GHC.Prim\n"
657 ++ "import GHC.Tuple ()\n"
658 ++ "import GHC.Prim (" ++ types
++ ")\n"
659 ++ unlines (concatMap f specs
)
661 specs
= filter (not.dodgy
) $
662 filter (not.is_llvm_only
) $
663 filter is_primop entries
664 tycons
= foldr union [] $ map (tyconsIn
. ty
) specs
665 tycons
' = filter (`
notElem`
[TyCon
"()", TyCon
"Bool"]) tycons
666 types
= concat $ intersperse ", " $ map show tycons
'
667 f spec
= let args
= map (\n -> "a" ++ show n
) [1 .. arity
(ty spec
)]
668 src_name
= wrap
(name spec
)
669 lhs
= src_name
++ " " ++ unwords args
670 rhs
= "(GHC.Prim." ++ name spec
++ ") " ++ unwords args
671 in ["{-# NOINLINE " ++ src_name
++ " #-}",
672 src_name
++ " :: " ++ pprTy
(ty spec
),
674 wrap nm |
isLower (head nm
) = nm
675 |
otherwise = "(" ++ nm
++ ")"
679 [-- C code generator can't handle these
682 -- not interested in parallel support
683 "par#", "parGlobal#", "parLocal#", "parAt#",
684 "parAtAbs#", "parAtRel#", "parAtForNow#"
687 is_llvm_only
:: Entry
-> Bool
689 case lookup_attrib
"llvm_only" (opts entry
) of
690 Just
(OptionTrue _
) -> True
693 gen_primop_list
:: Info
-> String
694 gen_primop_list
(Info _ entries
)
696 [ " [" ++ cons first
]
698 map (\p
-> " , " ++ cons p
) rest
701 ) where (first
:rest
) = concatMap desugarVectorSpec
(filter is_primop entries
)
703 mIN_VECTOR_UNIQUE
:: Int
704 mIN_VECTOR_UNIQUE
= 300
706 gen_primop_vector_uniques
:: Info
-> String
707 gen_primop_vector_uniques
(Info _ entries
)
709 concatMap mkVecUnique
(specs `
zip`
[mIN_VECTOR_UNIQUE
..])
711 specs
= concatMap desugarVectorSpec
(filter is_vector
(filter is_primtype entries
))
713 mkVecUnique
:: (Entry
, Int) -> [String]
714 mkVecUnique
(i
, unique
) =
715 [ key_id
++ " :: Unique"
716 , key_id
++ " = mkPreludeTyConUnique " ++ show unique
719 key_id
= prefix i
++ "PrimTyConKey"
721 gen_primop_vector_tys
:: Info
-> String
722 gen_primop_vector_tys
(Info _ entries
)
724 concatMap mkVecTypes specs
726 specs
= concatMap desugarVectorSpec
(filter is_vector
(filter is_primtype entries
))
728 mkVecTypes
:: Entry
-> [String]
730 [ name_id
++ " :: Name"
731 , name_id
++ " = mkPrimTc (fsLit \"" ++ pprTy
(ty i
) ++ "\") " ++ key_id
++ " " ++ tycon_id
732 , ty_id
++ " :: Type"
733 , ty_id
++ " = mkTyConTy " ++ tycon_id
734 , tycon_id
++ " :: TyCon"
735 , tycon_id
++ " = pcPrimTyCon0 " ++ name_id
++
736 " (VecRep " ++ show (veclen i
) ++ " " ++ elemrep i
++ ")"
739 key_id
= prefix i
++ "PrimTyConKey"
740 name_id
= prefix i
++ "PrimTyConName"
741 ty_id
= prefix i
++ "PrimTy"
742 tycon_id
= prefix i
++ "PrimTyCon"
744 gen_primop_vector_tys_exports
:: Info
-> String
745 gen_primop_vector_tys_exports
(Info _ entries
)
749 specs
= concatMap desugarVectorSpec
(filter is_vector
(filter is_primtype entries
))
751 mkVecTypes
:: Entry
-> String
753 "\t" ++ ty_id
++ ", " ++ tycon_id
++ ","
755 ty_id
= prefix i
++ "PrimTy"
756 tycon_id
= prefix i
++ "PrimTyCon"
758 gen_primop_vector_tycons
:: Info
-> String
759 gen_primop_vector_tycons
(Info _ entries
)
763 specs
= concatMap desugarVectorSpec
(filter is_vector
(filter is_primtype entries
))
765 mkVecTypes
:: Entry
-> String
769 tycon_id
= prefix i
++ "PrimTyCon"
771 gen_primop_tag
:: Info
-> String
772 gen_primop_tag
(Info _ entries
)
773 = unlines (max_def_type
: max_def
:
774 tagOf_type
: zipWith f primop_entries
[1 :: Int ..])
776 primop_entries
= concatMap desugarVectorSpec
$ filter is_primop entries
777 tagOf_type
= "tagOf_PrimOp :: PrimOp -> FastInt"
778 f i n
= "tagOf_PrimOp " ++ cons i
++ " = _ILIT(" ++ show n
++ ")"
779 max_def_type
= "maxPrimOpTag :: Int"
780 max_def
= "maxPrimOpTag = " ++ show (length primop_entries
)
782 gen_data_decl
:: Info
-> String
783 gen_data_decl
(Info _ entries
) =
784 "data PrimOp\n = " ++ head conss
++ "\n"
785 ++ unlines (map (" | "++) (tail conss
))
787 conss
= map genCons
(filter is_primop entries
)
789 genCons
:: Entry
-> String
791 case vecOptions entry
of
793 _
-> cons entry
++ " PrimOpVecCat Length Width"
795 gen_switch_from_attribs
:: String -> String -> Info
-> String
796 gen_switch_from_attribs attrib_name fn_name
(Info defaults entries
)
797 = let defv
= lookup_attrib attrib_name defaults
798 alternatives
= catMaybes (map mkAlt
(filter is_primop entries
))
800 getAltRhs
(OptionFalse _
) = "False"
801 getAltRhs
(OptionTrue _
) = "True"
802 getAltRhs
(OptionInteger _ i
) = show i
803 getAltRhs
(OptionString _ s
) = s
804 getAltRhs
(OptionVector _
) = "True"
805 getAltRhs
(OptionFixity mf
) = show mf
808 = case lookup_attrib attrib_name
(opts po
) of
810 Just xx
-> case vecOptions po
of
811 [] -> Just
(fn_name
++ " " ++ cons po
++ " = " ++ getAltRhs xx
)
812 _
-> Just
(fn_name
++ " (" ++ cons po
++ " _ _ _) = " ++ getAltRhs xx
)
816 Nothing
-> error ("gen_switch_from: " ++ attrib_name
)
818 -> unlines alternatives
819 ++ fn_name
++ " _ = " ++ getAltRhs xx
++ "\n"
821 ------------------------------------------------------------------
822 -- Create PrimOpInfo text from PrimOpSpecs -----------------------
823 ------------------------------------------------------------------
825 gen_primop_info
:: Info
-> String
826 gen_primop_info
(Info _ entries
)
827 = unlines (map mkPOItext
(concatMap desugarVectorSpec
(filter is_primop entries
)))
829 mkPOItext
:: Entry
-> String
830 mkPOItext i
= mkPOI_LHS_text i
++ mkPOI_RHS_text i
832 mkPOI_LHS_text
:: Entry
-> String
834 = "primOpInfo " ++ cons i
++ " = "
836 mkPOI_RHS_text
:: Entry
-> String
842 -> "mkCompare " ++ sl_name i
++ ppType t1
843 _
-> error "Type error in comparison op"
847 -> "mkMonadic " ++ sl_name i
++ ppType t1
848 _
-> error "Type error in monadic op"
852 -> "mkDyadic " ++ sl_name i
++ ppType t1
853 _
-> error "Type error in dyadic op"
855 -> let (argTys
, resTy
) = flatTys
(ty i
)
856 tvs
= nub (tvsIn
(ty i
))
858 "mkGenPrimOp " ++ sl_name i
++ " "
859 ++ listify
(map ppTyVar tvs
) ++ " "
860 ++ listify
(map ppType argTys
) ++ " "
861 ++ "(" ++ ppType resTy
++ ")"
863 sl_name
:: Entry
-> String
864 sl_name i
= "(fsLit \"" ++ name i
++ "\") "
866 ppTyVar
:: String -> String
867 ppTyVar
"a" = "alphaTyVar"
868 ppTyVar
"b" = "betaTyVar"
869 ppTyVar
"c" = "gammaTyVar"
870 ppTyVar
"s" = "deltaTyVar"
871 ppTyVar
"o" = "openAlphaTyVar"
872 ppTyVar _
= error "Unknown type var"
874 ppType
:: Ty
-> String
875 ppType
(TyApp
(TyCon
"Any") []) = "anyTy"
876 ppType
(TyApp
(TyCon
"Bool") []) = "boolTy"
878 ppType
(TyApp
(TyCon
"Int#") []) = "intPrimTy"
879 ppType
(TyApp
(TyCon
"Int32#") []) = "int32PrimTy"
880 ppType
(TyApp
(TyCon
"Int64#") []) = "int64PrimTy"
881 ppType
(TyApp
(TyCon
"Char#") []) = "charPrimTy"
882 ppType
(TyApp
(TyCon
"Word#") []) = "wordPrimTy"
883 ppType
(TyApp
(TyCon
"Word32#") []) = "word32PrimTy"
884 ppType
(TyApp
(TyCon
"Word64#") []) = "word64PrimTy"
885 ppType
(TyApp
(TyCon
"Addr#") []) = "addrPrimTy"
886 ppType
(TyApp
(TyCon
"Float#") []) = "floatPrimTy"
887 ppType
(TyApp
(TyCon
"Double#") []) = "doublePrimTy"
888 ppType
(TyApp
(TyCon
"ByteArray#") []) = "byteArrayPrimTy"
889 ppType
(TyApp
(TyCon
"RealWorld") []) = "realWorldTy"
890 ppType
(TyApp
(TyCon
"ThreadId#") []) = "threadIdPrimTy"
891 ppType
(TyApp
(TyCon
"ForeignObj#") []) = "foreignObjPrimTy"
892 ppType
(TyApp
(TyCon
"BCO#") []) = "bcoPrimTy"
893 ppType
(TyApp
(TyCon
"()") []) = "unitTy" -- unitTy is TysWiredIn's name for ()
895 ppType
(TyVar
"a") = "alphaTy"
896 ppType
(TyVar
"b") = "betaTy"
897 ppType
(TyVar
"c") = "gammaTy"
898 ppType
(TyVar
"s") = "deltaTy"
899 ppType
(TyVar
"o") = "openAlphaTy"
901 ppType
(TyApp
(TyCon
"State#") [x
]) = "mkStatePrimTy " ++ ppType x
902 ppType
(TyApp
(TyCon
"MutVar#") [x
,y
]) = "mkMutVarPrimTy " ++ ppType x
904 ppType
(TyApp
(TyCon
"MutableArray#") [x
,y
]) = "mkMutableArrayPrimTy " ++ ppType x
906 ppType
(TyApp
(TyCon
"MutableArrayArray#") [x
]) = "mkMutableArrayArrayPrimTy " ++ ppType x
907 ppType
(TyApp
(TyCon
"MutableByteArray#") [x
]) = "mkMutableByteArrayPrimTy "
909 ppType
(TyApp
(TyCon
"Array#") [x
]) = "mkArrayPrimTy " ++ ppType x
910 ppType
(TyApp
(TyCon
"ArrayArray#") []) = "mkArrayArrayPrimTy"
913 ppType
(TyApp
(TyCon
"Weak#") [x
]) = "mkWeakPrimTy " ++ ppType x
914 ppType
(TyApp
(TyCon
"StablePtr#") [x
]) = "mkStablePtrPrimTy " ++ ppType x
915 ppType
(TyApp
(TyCon
"StableName#") [x
]) = "mkStableNamePrimTy " ++ ppType x
917 ppType
(TyApp
(TyCon
"MVar#") [x
,y
]) = "mkMVarPrimTy " ++ ppType x
919 ppType
(TyApp
(TyCon
"TVar#") [x
,y
]) = "mkTVarPrimTy " ++ ppType x
922 ppType
(TyApp
(VecTyCon _ pptc
) []) = pptc
924 ppType
(TyUTup ts
) = "(mkTupleTy UnboxedTuple "
925 ++ listify
(map ppType ts
) ++ ")"
927 ppType
(TyF s d
) = "(mkFunTy (" ++ ppType s
++ ") (" ++ ppType d
++ "))"
928 ppType
(TyC s d
) = "(mkFunTy (" ++ ppType s
++ ") (" ++ ppType d
++ "))"
931 = error ("ppType: can't handle: " ++ show other
++ "\n")
933 pprFixityDir
:: FixityDirection
-> String
934 pprFixityDir InfixN
= "infix"
935 pprFixityDir InfixL
= "infixl"
936 pprFixityDir InfixR
= "infixr"
938 listify
:: [String] -> String
939 listify ss
= "[" ++ concat (intersperse ", " ss
) ++ "]"
941 flatTys
:: Ty
-> ([Ty
],Ty
)
942 flatTys
(TyF t1 t2
) = case flatTys t2
of (ts
,t
) -> (t1
:ts
,t
)
943 flatTys
(TyC t1 t2
) = case flatTys t2
of (ts
,t
) -> (t1
:ts
,t
)
944 flatTys other
= ([],other
)
946 tvsIn
:: Ty
-> [TyVar
]
947 tvsIn
(TyF t1 t2
) = tvsIn t1
++ tvsIn t2
948 tvsIn
(TyC t1 t2
) = tvsIn t1
++ tvsIn t2
949 tvsIn
(TyApp _ tys
) = concatMap tvsIn tys
950 tvsIn
(TyVar tv
) = [tv
]
951 tvsIn
(TyUTup tys
) = concatMap tvsIn tys
953 tyconsIn
:: Ty
-> [TyCon
]
954 tyconsIn
(TyF t1 t2
) = tyconsIn t1 `
union` tyconsIn t2
955 tyconsIn
(TyC t1 t2
) = tyconsIn t1 `
union` tyconsIn t2
956 tyconsIn
(TyApp tc tys
) = foldr union [tc
] $ map tyconsIn tys
957 tyconsIn
(TyVar _
) = []
958 tyconsIn
(TyUTup tys
) = foldr union [] $ map tyconsIn tys
961 arity
= length . fst . flatTys