Merge branch 'cλash' of http://git.stderr.nl/matthijs/projects/master-project
[matthijs/master-project/cλash.git] / VHDLTools.hs
1 module VHDLTools where
2
3 -- Standard modules
4 import qualified Maybe
5 import qualified Data.List as List
6 import qualified Data.Map as Map
7 import qualified Control.Monad as Monad
8 import qualified Control.Arrow as Arrow
9 import qualified Data.Monoid as Monoid
10 import Data.Accessor
11
12 -- ForSyDe
13 import qualified ForSyDe.Backend.VHDL.AST as AST
14
15 -- GHC API
16 import CoreSyn
17 import qualified Name
18 import qualified OccName
19 import qualified Var
20 import qualified Id
21 import qualified TyCon
22 import qualified Type
23 import qualified DataCon
24 import qualified CoreSubst
25
26 -- Local imports
27 import VHDLTypes
28 import CoreTools
29 import Pretty
30 import Constants
31
32 -----------------------------------------------------------------------------
33 -- Functions to generate concurrent statements
34 -----------------------------------------------------------------------------
35
36 -- Create an unconditional assignment statement
37 mkUncondAssign ::
38   Either CoreBndr AST.VHDLName -- ^ The signal to assign to
39   -> AST.Expr -- ^ The expression to assign
40   -> AST.ConcSm -- ^ The resulting concurrent statement
41 mkUncondAssign dst expr = mkAssign dst Nothing expr
42
43 -- Create a conditional assignment statement
44 mkCondAssign ::
45   Either CoreBndr AST.VHDLName -- ^ The signal to assign to
46   -> AST.Expr -- ^ The condition
47   -> AST.Expr -- ^ The value when true
48   -> AST.Expr -- ^ The value when false
49   -> AST.ConcSm -- ^ The resulting concurrent statement
50 mkCondAssign dst cond true false = mkAssign dst (Just (cond, true)) false
51
52 -- Create a conditional or unconditional assignment statement
53 mkAssign ::
54   Either CoreBndr AST.VHDLName -> -- ^ The signal to assign to
55   Maybe (AST.Expr , AST.Expr) -> -- ^ Optionally, the condition to test for
56                                  -- and the value to assign when true.
57   AST.Expr -> -- ^ The value to assign when false or no condition
58   AST.ConcSm -- ^ The resulting concurrent statement
59 mkAssign dst cond false_expr =
60   let
61     -- I'm not 100% how this assignment AST works, but this gets us what we
62     -- want...
63     whenelse = case cond of
64       Just (cond_expr, true_expr) -> 
65         let 
66           true_wform = AST.Wform [AST.WformElem true_expr Nothing] 
67         in
68           [AST.WhenElse true_wform cond_expr]
69       Nothing -> []
70     false_wform = AST.Wform [AST.WformElem false_expr Nothing]
71     dst_name  = case dst of
72       Left bndr -> AST.NSimple (varToVHDLId bndr)
73       Right name -> name
74     assign    = dst_name AST.:<==: (AST.ConWforms whenelse false_wform Nothing)
75   in
76     AST.CSSASm assign
77
78 mkAssocElems :: 
79   [CoreSyn.CoreExpr]            -- | The argument that are applied to function
80   -> CoreSyn.CoreBndr           -- | The binder in which to store the result
81   -> Entity                     -- | The entity to map against.
82   -> [AST.AssocElem]            -- | The resulting port maps
83 mkAssocElems args res entity =
84     -- Create the actual AssocElems
85     Maybe.catMaybes $ zipWith mkAssocElem ports sigs
86   where
87     -- Turn the ports and signals from a map into a flat list. This works,
88     -- since the maps must have an identical form by definition. TODO: Check
89     -- the similar form?
90     arg_ports = ent_args entity
91     res_port  = ent_res entity
92     -- Extract the id part from the (id, type) tuple
93     ports     = map (Monad.liftM fst) (res_port : arg_ports)
94     -- Translate signal numbers into names
95     sigs      = (varToString res : map (varToString.exprToVar) args)
96
97 -- | Create an VHDL port -> signal association
98 mkAssocElem :: Maybe AST.VHDLId -> String -> Maybe AST.AssocElem
99 mkAssocElem (Just port) signal = Just $ Just port AST.:=>: (AST.ADName (AST.NSimple (mkVHDLExtId signal))) 
100 mkAssocElem Nothing _ = Nothing
101
102 -- | Create an VHDL port -> signal association
103 mkAssocElemIndexed :: Maybe AST.VHDLId -> String -> AST.VHDLId -> Maybe AST.AssocElem
104 mkAssocElemIndexed (Just port) signal index = Just $ Just port AST.:=>: (AST.ADName (AST.NIndexed (AST.IndexedName 
105                       (AST.NSimple (mkVHDLExtId signal)) [AST.PrimName $ AST.NSimple index])))
106 mkAssocElemIndexed Nothing _ _ = Nothing
107
108 mkComponentInst ::
109   String -- ^ The portmap label
110   -> AST.VHDLId -- ^ The entity name
111   -> [AST.AssocElem] -- ^ The port assignments
112   -> AST.ConcSm
113 mkComponentInst label entity_id portassigns = AST.CSISm compins
114   where
115     compins = AST.CompInsSm (mkVHDLExtId label) (AST.IUEntity (AST.NSimple entity_id)) (AST.PMapAspect portassigns)
116
117 -----------------------------------------------------------------------------
118 -- Functions to generate VHDL Exprs
119 -----------------------------------------------------------------------------
120
121 -- Turn a variable reference into a AST expression
122 varToVHDLExpr :: Var.Var -> AST.Expr
123 varToVHDLExpr var = 
124   case Id.isDataConWorkId_maybe var of
125     Just dc -> dataconToVHDLExpr dc
126     -- This is a dataconstructor.
127     -- Not a datacon, just another signal. Perhaps we should check for
128     -- local/global here as well?
129     Nothing -> AST.PrimName $ AST.NSimple $ varToVHDLId var
130
131 -- Turn a alternative constructor into an AST expression. For
132 -- dataconstructors, this is only the constructor itself, not any arguments it
133 -- has. Should not be called with a DEFAULT constructor.
134 altconToVHDLExpr :: CoreSyn.AltCon -> AST.Expr
135 altconToVHDLExpr (DataAlt dc) = dataconToVHDLExpr dc
136
137 altconToVHDLExpr (LitAlt _) = error "VHDL.conToVHDLExpr Literals not support in case alternatives yet"
138 altconToVHDLExpr DEFAULT = error "VHDL.conToVHDLExpr DEFAULT alternative should not occur here!"
139
140 -- Turn a datacon (without arguments!) into a VHDL expression.
141 dataconToVHDLExpr :: DataCon.DataCon -> AST.Expr
142 dataconToVHDLExpr dc = AST.PrimLit lit
143   where
144     tycon = DataCon.dataConTyCon dc
145     tyname = TyCon.tyConName tycon
146     dcname = DataCon.dataConName dc
147     lit = case Name.getOccString tyname of
148       -- TODO: Do something more robust than string matching
149       "Bit"      -> case Name.getOccString dcname of "High" -> "'1'"; "Low" -> "'0'"
150       "Bool" -> case Name.getOccString dcname of "True" -> "true"; "False" -> "false"
151
152 -----------------------------------------------------------------------------
153 -- Functions dealing with names, variables and ids
154 -----------------------------------------------------------------------------
155
156 -- Creates a VHDL Id from a binder
157 varToVHDLId ::
158   CoreSyn.CoreBndr
159   -> AST.VHDLId
160 varToVHDLId = mkVHDLExtId . OccName.occNameString . Name.nameOccName . Var.varName
161
162 -- Extracts the binder name as a String
163 varToString ::
164   CoreSyn.CoreBndr
165   -> String
166 varToString = OccName.occNameString . Name.nameOccName . Var.varName
167
168 -- Get the string version a Var's unique
169 varToStringUniq :: Var.Var -> String
170 varToStringUniq = show . Var.varUnique
171
172 -- Extracts the string version of the name
173 nameToString :: Name.Name -> String
174 nameToString = OccName.occNameString . Name.nameOccName
175
176 -- Shortcut for Basic VHDL Ids.
177 -- Can only contain alphanumerics and underscores. The supplied string must be
178 -- a valid basic id, otherwise an error value is returned. This function is
179 -- not meant to be passed identifiers from a source file, use mkVHDLExtId for
180 -- that.
181 mkVHDLBasicId :: String -> AST.VHDLId
182 mkVHDLBasicId s = 
183   AST.unsafeVHDLBasicId $ (strip_multiscore . strip_leading . strip_invalid) s
184   where
185     -- Strip invalid characters.
186     strip_invalid = filter (`elem` ['A'..'Z'] ++ ['a'..'z'] ++ ['0'..'9'] ++ "_.")
187     -- Strip leading numbers and underscores
188     strip_leading = dropWhile (`elem` ['0'..'9'] ++ "_")
189     -- Strip multiple adjacent underscores
190     strip_multiscore = concat . map (\cs -> 
191         case cs of 
192           ('_':_) -> "_"
193           _ -> cs
194       ) . List.group
195
196 -- Shortcut for Extended VHDL Id's. These Id's can contain a lot more
197 -- different characters than basic ids, but can never be used to refer to
198 -- basic ids.
199 -- Use extended Ids for any values that are taken from the source file.
200 mkVHDLExtId :: String -> AST.VHDLId
201 mkVHDLExtId s = 
202   AST.unsafeVHDLExtId $ strip_invalid s
203   where 
204     -- Allowed characters, taken from ForSyde's mkVHDLExtId
205     allowed = ['A'..'Z'] ++ ['a'..'z'] ++ ['0'..'9'] ++ " \"#&\\'()*+,./:;<=>_|!$%@?[]^`{}~-"
206     strip_invalid = filter (`elem` allowed)
207
208 -- Create a record field selector that selects the given label from the record
209 -- stored in the given binder.
210 mkSelectedName :: CoreBndr -> AST.VHDLId -> AST.VHDLName
211 mkSelectedName bndr label =
212   let 
213     sel_prefix = AST.NSimple $ varToVHDLId bndr
214     sel_suffix = AST.SSimple $ label
215   in
216     AST.NSelected $ sel_prefix AST.:.: sel_suffix 
217
218 -----------------------------------------------------------------------------
219 -- Functions dealing with VHDL types
220 -----------------------------------------------------------------------------
221
222 -- | Maps the string name (OccName) of a type to the corresponding VHDL type,
223 -- for a few builtin types.
224 builtin_types = 
225   Map.fromList [
226     ("Bit", std_logicTM),
227     ("Bool", booleanTM) -- TysWiredIn.boolTy
228   ]
229
230 -- Translate a Haskell type to a VHDL type, generating a new type if needed.
231 vhdl_ty :: Type.Type -> VHDLSession AST.TypeMark
232 vhdl_ty ty = do
233   typemap <- getA vsTypes
234   let builtin_ty = do -- See if this is a tycon and lookup its name
235         (tycon, args) <- Type.splitTyConApp_maybe ty
236         let name = Name.getOccString (TyCon.tyConName tycon)
237         Map.lookup name builtin_types
238   -- If not a builtin type, try the custom types
239   let existing_ty = (fmap fst) $ Map.lookup (OrdType ty) typemap
240   case Monoid.getFirst $ Monoid.mconcat (map Monoid.First [builtin_ty, existing_ty]) of
241     -- Found a type, return it
242     Just t -> return t
243     -- No type yet, try to construct it
244     Nothing -> do
245       newty_maybe <- (construct_vhdl_ty ty)
246       case newty_maybe of
247         Just (ty_id, ty_def) -> do
248           -- TODO: Check name uniqueness
249           modA vsTypes (Map.insert (OrdType ty) (ty_id, ty_def))
250           return ty_id
251         Nothing -> error $ "Unsupported Haskell type: " ++ pprString ty
252
253 -- Construct a new VHDL type for the given Haskell type.
254 construct_vhdl_ty :: Type.Type -> VHDLSession (Maybe (AST.TypeMark, Either AST.TypeDef AST.SubtypeIn))
255 construct_vhdl_ty ty = do
256   case Type.splitTyConApp_maybe ty of
257     Just (tycon, args) -> do
258       let name = Name.getOccString (TyCon.tyConName tycon)
259       case name of
260         "TFVec" -> do
261           res <- mk_vector_ty (tfvec_len ty) (tfvec_elem ty)
262           return $ Just $ (Arrow.second Right) res
263         -- "SizedWord" -> do
264         --   res <- mk_vector_ty (sized_word_len ty) ty
265         --   return $ Just $ (Arrow.second Left) res
266         "RangedWord" -> do 
267           res <- mk_natural_ty 0 (ranged_word_bound ty)
268           return $ Just $ (Arrow.second Right) res
269         -- Create a custom type from this tycon
270         otherwise -> mk_tycon_ty tycon args
271     Nothing -> return $ Nothing
272
273 -- | Create VHDL type for a custom tycon
274 mk_tycon_ty :: TyCon.TyCon -> [Type.Type] -> VHDLSession (Maybe (AST.TypeMark, Either AST.TypeDef AST.SubtypeIn))
275 mk_tycon_ty tycon args =
276   case TyCon.tyConDataCons tycon of
277     -- Not an algebraic type
278     [] -> error $ "Only custom algebraic types are supported: " ++ pprString tycon
279     [dc] -> do
280       let arg_tys = DataCon.dataConRepArgTys dc
281       -- TODO: CoreSubst docs say each Subs can be applied only once. Is this a
282       -- violation? Or does it only mean not to apply it again to the same
283       -- subject?
284       let real_arg_tys = map (CoreSubst.substTy subst) arg_tys
285       elem_tys <- mapM vhdl_ty real_arg_tys
286       let elems = zipWith AST.ElementDec recordlabels elem_tys
287       -- For a single construct datatype, build a record with one field for
288       -- each argument.
289       -- TODO: Add argument type ids to this, to ensure uniqueness
290       -- TODO: Special handling for tuples?
291       let ty_id = mkVHDLExtId $ nameToString (TyCon.tyConName tycon)
292       let ty_def = AST.TDR $ AST.RecordTypeDef elems
293       return $ Just (ty_id, Left ty_def)
294     dcs -> error $ "Only single constructor datatypes supported: " ++ pprString tycon
295   where
296     -- Create a subst that instantiates all types passed to the tycon
297     -- TODO: I'm not 100% sure that this is the right way to do this. It seems
298     -- to work so far, though..
299     tyvars = TyCon.tyConTyVars tycon
300     subst = CoreSubst.extendTvSubstList CoreSubst.emptySubst (zip tyvars args)
301     -- Generate a bunch of labels for fields of a record
302     recordlabels = map (\c -> mkVHDLBasicId [c]) ['A'..'Z']
303
304 -- | Create a VHDL vector type
305 mk_vector_ty ::
306   Int -- ^ The length of the vector
307   -> Type.Type -- ^ The Haskell element type of the Vector
308   -> VHDLSession (AST.TypeMark, AST.SubtypeIn) -- The typemark created.
309
310 mk_vector_ty len el_ty = do
311   elem_types_map <- getA vsElemTypes
312   el_ty_tm <- vhdl_ty el_ty
313   let ty_id = mkVHDLExtId $ "vector-"++ (AST.fromVHDLId el_ty_tm) ++ "-0_to_" ++ (show len)
314   let range = AST.ConstraintIndex $ AST.IndexConstraint [AST.ToRange (AST.PrimLit "0") (AST.PrimLit $ show (len - 1))]
315   let existing_elem_ty = (fmap fst) $ Map.lookup (OrdType el_ty) elem_types_map
316   case existing_elem_ty of
317     Just t -> do
318       let ty_def = AST.SubtypeIn t (Just range)
319       return (ty_id, ty_def)
320     Nothing -> do
321       let vec_id = mkVHDLExtId $ "vector_" ++ (AST.fromVHDLId el_ty_tm)
322       let vec_def = AST.TDA $ AST.UnconsArrayDef [tfvec_indexTM] el_ty_tm
323       modA vsElemTypes (Map.insert (OrdType el_ty) (vec_id, vec_def))
324       --modA vsTypeFuns (Map.insert (OrdType el_ty) (genUnconsVectorFuns el_ty_tm vec_id)) 
325       let ty_def = AST.SubtypeIn vec_id (Just range)
326       return (ty_id, ty_def)
327
328 mk_natural_ty ::
329   Int -- ^ The minimum bound (> 0)
330   -> Int -- ^ The maximum bound (> minimum bound)
331   -> VHDLSession (AST.TypeMark, AST.SubtypeIn) -- The typemark created.
332 mk_natural_ty min_bound max_bound = do
333   let ty_id = mkVHDLExtId $ "nat_" ++ (show min_bound) ++ "_to_" ++ (show max_bound)
334   let range = AST.ConstraintRange $ AST.SubTypeRange (AST.PrimLit $ (show min_bound)) (AST.PrimLit $ (show max_bound))
335   let ty_def = AST.SubtypeIn naturalTM (Just range)
336   return (ty_id, ty_def)
337
338 -- Finds the field labels for VHDL type generated for the given Core type,
339 -- which must result in a record type.
340 getFieldLabels :: Type.Type -> VHDLSession [AST.VHDLId]
341 getFieldLabels ty = do
342   -- Ensure that the type is generated (but throw away it's VHDLId)
343   vhdl_ty ty
344   -- Get the types map, lookup and unpack the VHDL TypeDef
345   types <- getA vsTypes
346   case Map.lookup (OrdType ty) types of
347     Just (_, Left (AST.TDR (AST.RecordTypeDef elems))) -> return $ map (\(AST.ElementDec id _) -> id) elems
348     _ -> error $ "VHDL.getFieldLabels Type not found or not a record type? This should not happen! Type: " ++ (show ty)