vectoriser: adapt to new superclass story part I (dictionary construction)
[ghc-hetmet.git] / compiler / vectorise / Vectorise / Builtins / Base.hs
1
2 -- | Builtin types and functions used by the vectoriser.
3 --   These are all defined in the DPH package.
4 module Vectorise.Builtins.Base (
5         -- * Hard config
6         mAX_DPH_PROD,
7         mAX_DPH_SUM,
8         mAX_DPH_COMBINE,
9         mAX_DPH_SCALAR_ARGS,
10         
11         -- * Builtins
12         Builtins(..),
13         indexBuiltin,
14         
15         -- * Projections
16         selTy,
17         selReplicate,
18         selPick,
19         selTags,
20         selElements,
21         sumTyCon,
22         prodTyCon,
23         prodDataCon,
24         combinePDVar,
25         scalarZip,
26         closureCtrFun
27 ) where
28 import Vectorise.Builtins.Modules
29 import BasicTypes
30 import Class
31 import CoreSyn
32 import TysWiredIn
33 import Type
34 import TyCon
35 import DataCon
36 import Var
37 import Outputable
38 import Data.Array
39
40
41 -- Numbers of things exported by the DPH library.
42 mAX_DPH_PROD :: Int
43 mAX_DPH_PROD = 5
44
45 mAX_DPH_SUM :: Int
46 mAX_DPH_SUM = 2
47
48 mAX_DPH_COMBINE :: Int
49 mAX_DPH_COMBINE = 2
50
51 mAX_DPH_SCALAR_ARGS :: Int
52 mAX_DPH_SCALAR_ARGS = 3
53
54
55 -- | Holds the names of the builtin types and functions used by the vectoriser.
56 data Builtins 
57         = Builtins 
58         { dphModules       :: Modules
59
60         -- From dph-common:Data.Array.Parallel.Lifted.PArray
61         , parrayTyCon      :: TyCon                     -- ^ PArray
62         , parrayDataCon    :: DataCon                   -- ^ PArray
63         , pdataTyCon       :: TyCon                     -- ^ PData
64         , paTyCon          :: TyCon                     -- ^ PA
65         , paDataCon        :: DataCon                   -- ^ PA
66         , paPRSel          :: Var                       -- ^ PA
67         , preprTyCon       :: TyCon                     -- ^ PRepr
68         , prTyCon          :: TyCon                     -- ^ PR
69         , prDataCon        :: DataCon                   -- ^ PR
70         , replicatePDVar   :: Var                       -- ^ replicatePD
71         , emptyPDVar       :: Var                       -- ^ emptyPD
72         , packByTagPDVar   :: Var                       -- ^ packByTagPD
73         , combinePDVars    :: Array Int Var             -- ^ combinePD
74         , scalarClass      :: Class                     -- ^ Scalar
75
76         -- From dph-common:Data.Array.Parallel.Lifted.Closure
77         , closureTyCon     :: TyCon                     -- ^ :->
78         , closureVar       :: Var                       -- ^ closure
79         , applyVar         :: Var                       -- ^ $: 
80         , liftedClosureVar :: Var                       -- ^ liftedClosure
81         , liftedApplyVar   :: Var                       -- ^ liftedApply
82         , closureCtrFuns   :: Array Int Var             -- ^ closure1 .. closure2
83
84         -- From dph-common:Data.Array.Parallel.Lifted.Repr
85         , voidTyCon        :: TyCon                     -- ^ Void
86         , wrapTyCon        :: TyCon                     -- ^ Wrap
87         , sumTyCons        :: Array Int TyCon           -- ^ Sum2 .. Sum3
88         , voidVar          :: Var                       -- ^ void
89         , pvoidVar         :: Var                       -- ^ pvoid
90         , fromVoidVar      :: Var                       -- ^ fromVoid
91         , punitVar         :: Var                       -- ^ punit
92
93         -- From dph-common:Data.Array.Parallel.Lifted.Selector
94         , selTys           :: Array Int Type            -- ^ Sel2
95         , selReplicates    :: Array Int CoreExpr        -- ^ replicate2
96         , selPicks         :: Array Int CoreExpr        -- ^ pick2
97         , selTagss         :: Array Int CoreExpr        -- ^ tagsSel2
98         , selEls           :: Array (Int, Int) CoreExpr -- ^ elementsSel2_0 .. elementsSel_2_1
99
100         -- From dph-common:Data.Array.Parallel.Lifted.Scalar
101         -- NOTE: map is counted as a zipWith fn with one argument array.
102         , scalarZips       :: Array Int Var             -- ^ map, zipWith, zipWith3
103
104         -- A Fresh variable
105         , liftingContext   :: Var                       -- ^ lc
106         }
107
108
109 -- | Get an element from one of the arrays of contained by a `Builtins`.
110 --   If the indexed thing is not in the array then panic.
111 indexBuiltin 
112         :: (Ix i, Outputable i) 
113         => String                       -- ^ Name of the selector we've used, for panic messages.
114         -> (Builtins -> Array i a)      -- ^ Field selector for the `Builtins`.
115         -> i                            -- ^ Index into the array.
116         -> Builtins 
117         -> a
118
119 indexBuiltin fn f i bi
120   | inRange (bounds xs) i = xs ! i
121   | otherwise             
122   = pprSorry "Vectorise.Builtins.indexBuiltin" 
123         (vcat   [ text ""
124                 , text "DPH builtin function '" <> text fn <> text "' of size '" <> ppr i <> text "' is not yet implemented."
125                 , text "This function does not appear in your source program, but it is needed"
126                 , text "to compile your code in the backend. This is a known, current limitation"
127                 , text "of DPH. If you want it to to work you should send mail to cvs-ghc@haskell.org"
128                 , text "and ask what you can do to help (it might involve some GHC hacking)."])
129
130   where xs = f bi
131
132
133 -- Projections ----------------------------------------------------------------
134 -- We use these wrappers instead of indexing the `Builtin` structure directly
135 -- because they give nicer panic messages if the indexed thing cannot be found.
136
137 selTy :: Int -> Builtins -> Type
138 selTy           = indexBuiltin "selTy" selTys
139
140 selReplicate :: Int -> Builtins -> CoreExpr
141 selReplicate    = indexBuiltin "selReplicate" selReplicates 
142
143 selPick :: Int -> Builtins -> CoreExpr
144 selPick         = indexBuiltin "selPick" selPicks
145
146 selTags :: Int -> Builtins -> CoreExpr
147 selTags         = indexBuiltin "selTags" selTagss
148
149 selElements :: Int -> Int -> Builtins -> CoreExpr
150 selElements i j = indexBuiltin "selElements" selEls (i,j)
151
152 sumTyCon :: Int -> Builtins -> TyCon
153 sumTyCon        = indexBuiltin "sumTyCon" sumTyCons
154
155 prodTyCon :: Int -> Builtins -> TyCon
156 prodTyCon n _
157         | n >= 2 && n <= mAX_DPH_PROD 
158         = tupleTyCon Boxed n
159
160         | otherwise
161         = pprPanic "prodTyCon" (ppr n)
162
163 prodDataCon :: Int -> Builtins -> DataCon
164 prodDataCon n bi 
165  = case tyConDataCons (prodTyCon n bi) of
166         [con]   -> con
167         _       -> pprPanic "prodDataCon" (ppr n)
168
169 combinePDVar :: Int -> Builtins -> Var
170 combinePDVar    = indexBuiltin "combinePDVar" combinePDVars
171
172 scalarZip :: Int -> Builtins -> Var
173 scalarZip       = indexBuiltin "scalarZip" scalarZips
174
175 closureCtrFun :: Int -> Builtins -> Var
176 closureCtrFun   = indexBuiltin "closureCtrFun" closureCtrFuns
177
178