[project @ 1996-01-08 20:28:12 by partain]
[ghc-hetmet.git] / ghc / compiler / prelude / TyPod.lhs
1 %************************************************************************
2 %*                                                                      *
3 \section[TyPod]{The Pod datatype}
4 %*                                                                      *
5 %************************************************************************
6 \begin{code}
7 #include "HsVersions.h"
8
9 module TyPod where
10
11 import PrelFuns         -- help functions, types and things
12 import TyInteger --ToDo:DPH: no such thing any more!
13 import TyProcs
14 import TyBool           ( boolTy )
15 import Unique
16
17 import AbsUniType       ( getUniDataTyCon_maybe , mkPodizedPodTyCon )
18 import Maybes
19 \end{code}
20
21 In the implementation of \DPHaskell{} for a SIMD machine, we adopt three
22 diffrent models of \POD{}s.
23
24 %************************************************************************
25 \subsection[User]{The Users model}
26 %************************************************************************
27 The users model of a \POD{} is outlined in ``Data Parallel Haskell: Mixing old
28 and new glue''\cite{hill:dpglue}. In this model, a \POD{} represents a
29 collection of index value pairs, where each index uniquely identifies a
30 single element of a \POD{}.  As \POD{}s are an abstraction of the processing
31 elements of a data parallel machine, we choose to collect the index value
32 pairs into a data type we call a `processor'.
33
34 The indices of a \POD{} can be thought of as a subset of the
35 integers\footnote{10/03/93: I've decided to change the index types of \POD{}'s
36 ---they are now Int's {\em not} Integer's. The use of the GMP package has
37 changed things, Integers are now special, and there's no way I'm going
38 to have time to implement them on the DAP. I would like Integers to be like
39 Ints, i.e a single boxed primitive value --- they are'nt like that any more.
40 I've therefore plumped for Int's as index values, which means indices
41 are restricted to 32bit signed values.}. We use
42 the Haskell class system to extend the range of possible types for the indices
43 such that any type that is an instance of the class {\tt Pid} (processor
44 identifier) may be used as an index type.
45
46 %************************************************************************
47 \subsection[prePodized]{The Core Syntax model before podization}
48 %************************************************************************
49 Desugaring of the abstract syntax introduces the overloaded operators
50 {\tt fromDomain} and {\tt toDomain} to convert the index types to integers.
51 We bring the \POD{} type and processor types closer together in the core
52 syntax; \POD{}s will have types such as {\tt <<Int,Int;Char>>} in
53 which the integer types before the ``;'' determine the position of an
54 element identified by those integers within a two dimensioned \POD{}
55 (i.e a matrix).
56 %************************************************************************
57 \subsection[postPodized]{The Core Syntax model after podization}
58 %************************************************************************
59 Things drastically change after podization. There are four different
60 variety of \POD{}s being used at runtime:
61 \begin{enumerate}
62 \item[Interface] A $k$ dimensional Interface \POD{} of $\alpha$'s is
63                  represented by a product type that contains a $k$ dimensional
64                  inside out \POD{} of Boolean values that determine at what
65                  processors the Interface \POD{} is to be defined; and a $k$
66                  dimensional inside out \POD{} of $\alpha$'s - the \POD{}s that
67                  the user manipulates in \POD{} comprehensions are all
68                  interface \POD{}'s --- see note **1** on efficiency below.
69
70 \item[Podized]   The remaining types of \POD{}s are invisible to the user
71                   - See the podization files for more details (even a bit
72                  sketchy their :-(
73
74 \item[Primitive] A $k$ dimensional unboxed \POD{} is a contiguous subset of
75                  primitive unboxed values - these will hopefully be the
76                  staple diet of Data Parallel evaluation. For non SIMD
77                  people, these are just like `C' arrays, except we can apply
78                  primitive parallel operations to them---for example add
79                  two arrays together.
80
81 \item[Hard luck] Hard luck \POD{}s are the ones that we cann't implement in a
82                  parallel manner - see podization files for more details.
83 \end{enumerate}
84
85 Note **1** : Efficiency of parallel functions.
86
87 There are various (trivial) laws concerning \POD{} comprehensions, such as
88
89 (vectorMap f) . (vectorMap g) == vectorMap (f.g)
90
91 The right of the above expressions is more ``efficient'' because we only
92 unbox the interface \POD{}, then check for undefined elements once in contrast
93 to twice in the left expression. Maybe theres some scope here for some
94 simplifications ??
95
96 %************************************************************************
97 %*                                                                      *
98 \section[User_POD]{The ``Users model'' of a Pod}
99 %*                                                                      *
100 %************************************************************************
101 \begin{code}
102 mkPodTy :: UniType -> UniType
103 mkPodTy ty = UniData podTyCon [ty]
104
105 mkPodNTy:: Int -> UniType -> UniType
106 mkPodNTy n ty = UniData podTyCon [mkProcessorTy (take n int_tys) ty]
107               where
108                  int_tys = integerTy : int_tys
109
110 podTyCon = pcDataTyCon podTyConKey pRELUDE_BUILTIN "Pod" [alpha_tv] []
111 \end{code}
112
113 %************************************************************************
114 %*                                                                      *
115 \section[Podized_POD]{The ``Podized model'' of a Pod}
116 %*                                                                      *
117 %************************************************************************
118 Theres a small problem with the following code, I wonder if anyone can help??
119
120 I have defined podized versions of TyCons, by wrapping a TyCon and an Int in
121 a PodizedTyCon (similiar to technique used for Ids). This is helpfull because
122 when tycons are attached to cases, they show that they are podized (I want
123 to preserve the info). TyCons are also used in the unitype world, the problem
124 being if I want a podized dictionary - I cannt just call getUniDataTyCon
125 to get me the dictionaries TyCon - it doesnt have one :-( What I've therefore
126 done is get the tycon out of a unitype if it has one, otherwise I use a
127 default podizedTyConKey which means the things podized, but dont ask anything
128 about it - (also for polymorphic types).
129
130 ToDo(hilly):    Using @getUniDataTyCon_maybe@ doesnt seem a good way of doing
131                 things...
132 \begin{code}
133 mkPodizedPodNTy:: Int -> UniType -> UniType
134 mkPodizedPodNTy n ty
135   = case (getUniDataTyCon_maybe ty) of
136      Nothing    ->let tc = pcDataTyCon (podizedPodTyConKey n) pRELUDE_BUILTIN
137                                        ("PodizedUnk"++show n) [alpha_tv] []
138                   in UniData tc [ty]
139
140      Just (tycon,_,_) ->UniData (mkPodizedPodTyCon n tycon) [ty]
141
142 \end{code}
143 %************************************************************************
144 %*                                                                      *
145 \section[Podized_POD]{The ``Interface model'' of a Pod}
146 %*                                                                      *
147 %************************************************************************
148 \begin{code}
149 mkInterfacePodNTy n ty
150   = UniData (interfacePodTyCon n) [mkPodizedPodNTy n ty]
151
152 interfacePodTyCon n
153   = pcDataTyCon interfacePodTyConKey pRELUDE_BUILTIN
154                 "InterPod" [alpha_tv] [mKINTERPOD_ID n]
155
156 mKINTERPOD_ID n
157   = pcDataCon interfacePodDataConKey pRELUDE_BUILTIN "MkInterPod"
158               [] [] [mkPodizedPodNTy n boolTy] (interfacePodTyCon n) nullSpecEnv
159 \end{code}