vectoriser: fix warning
[ghc-hetmet.git] / compiler / vectorise / Vectorise / Type / PADict.hs
1
2 module Vectorise.Type.PADict
3         (buildPADict)
4 where
5 import Vectorise.Monad
6 import Vectorise.Builtins
7 import Vectorise.Type.Repr
8 import Vectorise.Type.PRepr
9 import Vectorise.Type.PRDict
10 import Vectorise.Utils
11
12 import BasicTypes
13 import CoreSyn
14 import CoreUtils
15 import CoreUnfold
16 import TyCon
17 import Type
18 import TypeRep
19 import Id
20 import Var
21 import Name
22 import Class
23 import Outputable
24
25 -- debug                = False
26 -- dtrace s x   = if debug then pprTrace "Vectoris.Type.PADict" s x else x
27
28 -- | Build the PA dictionary for some type and hoist it to top level.
29 --   The PA dictionary holds fns that convert values to and from their vectorised representations.
30 buildPADict
31         :: TyCon        -- ^ tycon of the type being vectorised.
32         -> TyCon        -- ^ tycon of the type used for the vectorised representation.
33         -> TyCon        -- 
34         -> SumRepr      -- ^ representation used for the type being vectorised.
35         -> VM Var       -- ^ name of the top-level dictionary function.
36
37 buildPADict vect_tc prepr_tc arr_tc repr
38  = polyAbstract tvs $ \args ->
39  case args of
40   (_:_) -> pprPanic "Vectorise.Type.PADict.buildPADict" (text "why do we need superclass dicts?")
41   [] -> do
42       -- TODO: I'm forcing args to [] because I'm not sure why we need them.
43       --       class PA has superclass (PR (PRepr a)) but we're not using
44       --       the superclass dictionary to build the PA dictionary.
45
46       -- Get ids for each of the methods in the dictionary.
47       method_ids <- mapM (method args) paMethods
48
49       -- Expression to build the dictionary.
50       pa_dc  <- builtin paDataCon
51       let dict = mkLams (tvs ++ args)
52                $ mkConApp pa_dc
53                $ Type inst_ty : map (method_call args) method_ids
54
55       -- Build the type of the dictionary function.
56       pa_tc             <- builtin paTyCon
57       let Just pa_cls   = tyConClass_maybe pa_tc
58
59       let dfun_ty       = mkForAllTys tvs
60                         $ mkFunTys (map varType args) (PredTy $ ClassP pa_cls [inst_ty])
61
62       -- Set the unfolding for the inliner.
63       raw_dfun <- newExportedVar dfun_name dfun_ty
64       let dfun = raw_dfun `setIdUnfolding`  mkDFunUnfolding dfun_ty (map Var method_ids)
65                           `setInlinePragma` dfunInlinePragma
66
67       -- Add the new binding to the top-level environment.
68       hoistBinding dfun dict
69       return dfun
70   where
71     tvs       = tyConTyVars vect_tc
72     arg_tys   = mkTyVarTys tvs
73     inst_ty   = mkTyConApp vect_tc arg_tys
74
75     dfun_name = mkPADFunOcc (getOccName vect_tc)
76
77     method args (name, build)
78       = localV
79       $ do
80           expr     <- build vect_tc prepr_tc arr_tc repr
81           let body = mkLams (tvs ++ args) expr
82           raw_var  <- newExportedVar (method_name name) (exprType body)
83           let var  = raw_var
84                       `setIdUnfolding` mkInlineUnfolding (Just (length args)) body
85                       `setInlinePragma` alwaysInlinePragma
86           hoistBinding var body
87           return var
88
89     method_call args id = mkApps (Var id) (map Type arg_tys ++ map Var args)
90     method_name name    = mkVarOcc $ occNameString dfun_name ++ ('$' : name)
91
92
93 paMethods :: [(String, TyCon -> TyCon -> TyCon -> SumRepr -> VM CoreExpr)]
94 paMethods = [("dictPRepr",    buildPRDict),
95              ("toPRepr",      buildToPRepr),
96              ("fromPRepr",    buildFromPRepr),
97              ("toArrPRepr",   buildToArrPRepr),
98              ("fromArrPRepr", buildFromArrPRepr)]
99