Added support for empty TFVec's, Added Some more builtin functions
[matthijs/master-project/cλash.git] / VHDL.hs
1 --
2 -- Functions to generate VHDL from FlatFunctions
3 --
4 module VHDL where
5
6 -- Standard modules
7 import qualified Data.Foldable as Foldable
8 import qualified Data.List as List
9 import qualified Data.Map as Map
10 import qualified Maybe
11 import qualified Control.Monad as Monad
12 import qualified Control.Arrow as Arrow
13 import qualified Control.Monad.Trans.State as State
14 import qualified Data.Traversable as Traversable
15 import qualified Data.Monoid as Monoid
16 import Data.Accessor
17 import qualified Data.Accessor.MonadState as MonadState
18 import Text.Regex.Posix
19 import Debug.Trace
20
21 -- ForSyDe
22 import qualified ForSyDe.Backend.VHDL.AST as AST
23
24 -- GHC API
25 import CoreSyn
26 import qualified Type
27 import qualified Name
28 import qualified OccName
29 import qualified Var
30 import qualified Id
31 import qualified IdInfo
32 import qualified TyCon
33 import qualified TcType
34 import qualified DataCon
35 import qualified CoreSubst
36 import qualified CoreUtils
37 import Outputable ( showSDoc, ppr )
38
39 -- Local imports
40 import VHDLTypes
41 import Flatten
42 import FlattenTypes
43 import TranslatorTypes
44 import HsValueMap
45 import Pretty
46 import CoreTools
47 import Constants
48 import Generate
49 import GlobalNameTable
50
51 createDesignFiles ::
52   [(CoreSyn.CoreBndr, CoreSyn.CoreExpr)]
53   -> [(AST.VHDLId, AST.DesignFile)]
54
55 createDesignFiles binds =
56   (mkVHDLBasicId "types", AST.DesignFile ieee_context [type_package_dec, type_package_body]) :
57   map (Arrow.second $ AST.DesignFile full_context) units
58   
59   where
60     init_session = VHDLSession Map.empty Map.empty Map.empty Map.empty globalNameTable
61     (units, final_session) = 
62       State.runState (createLibraryUnits binds) init_session
63     tyfun_decls = Map.elems (final_session ^.vsTypeFuns)
64     ty_decls = map mktydecl $ Map.elems (final_session ^. vsTypes)
65     vec_decls = map (\(v_id, v_def) -> AST.PDITD $ AST.TypeDec v_id v_def) (Map.elems (final_session ^. vsElemTypes))
66     tfvec_index_decl = AST.PDISD $ AST.SubtypeDec tfvec_indexTM tfvec_index_def
67     tfvec_range = AST.ConstraintRange $ AST.SubTypeRange (AST.PrimLit "-1") (AST.PrimName $ AST.NAttribute $ AST.AttribName (AST.NSimple integerTM) highId Nothing)
68     tfvec_index_def = AST.SubtypeIn integerTM (Just tfvec_range)
69     ieee_context = [
70         AST.Library $ mkVHDLBasicId "IEEE",
71         mkUseAll ["IEEE", "std_logic_1164"],
72         mkUseAll ["IEEE", "numeric_std"]
73       ]
74     full_context =
75       mkUseAll ["work", "types"]
76       : ieee_context
77     type_package_dec = AST.LUPackageDec $ AST.PackageDec (mkVHDLBasicId "types") ([tfvec_index_decl] ++ vec_decls ++ ty_decls ++ subProgSpecs)
78     type_package_body = AST.LUPackageBody $ AST.PackageBody typesId (concat tyfun_decls)
79     subProgSpecs = concat (map subProgSpec tyfun_decls)
80     subProgSpec = map (\(AST.SubProgBody spec _ _) -> AST.PDISS spec)
81     mktydecl :: (AST.VHDLId, Either AST.TypeDef AST.SubtypeIn) -> AST.PackageDecItem
82     mktydecl (ty_id, Left ty_def) = AST.PDITD $ AST.TypeDec ty_id ty_def
83     mktydecl (ty_id, Right ty_def) = AST.PDISD $ AST.SubtypeDec ty_id ty_def
84
85 -- Create a use foo.bar.all statement. Takes a list of components in the used
86 -- name. Must contain at least two components
87 mkUseAll :: [String] -> AST.ContextItem
88 mkUseAll ss = 
89   AST.Use $ from AST.:.: AST.All
90   where
91     base_prefix = (AST.NSimple $ mkVHDLBasicId $ head ss)
92     from = foldl select base_prefix (tail ss)
93     select prefix s = AST.NSelected $ prefix AST.:.: (AST.SSimple $ mkVHDLBasicId s)
94       
95 createLibraryUnits ::
96   [(CoreSyn.CoreBndr, CoreSyn.CoreExpr)]
97   -> VHDLState [(AST.VHDLId, [AST.LibraryUnit])]
98
99 createLibraryUnits binds = do
100   entities <- Monad.mapM createEntity binds
101   archs <- Monad.mapM createArchitecture binds
102   return $ zipWith 
103     (\ent arch -> 
104       let AST.EntityDec id _ = ent in 
105       (id, [AST.LUEntity ent, AST.LUArch arch])
106     )
107     entities archs
108
109 -- | Create an entity for a given function
110 createEntity ::
111   (CoreSyn.CoreBndr, CoreSyn.CoreExpr) -- | The function
112   -> VHDLState AST.EntityDec -- | The resulting entity
113
114 createEntity (fname, expr) = do
115       -- Strip off lambda's, these will be arguments
116       let (args, letexpr) = CoreSyn.collectBinders expr
117       args' <- Monad.mapM mkMap args
118       -- There must be a let at top level 
119       let (CoreSyn.Let binds (CoreSyn.Var res)) = letexpr
120       res' <- mkMap res
121       let vhdl_id = mkVHDLBasicId $ bndrToString fname ++ "_" ++ varToStringUniq fname
122       let ent_decl' = createEntityAST vhdl_id args' res'
123       let AST.EntityDec entity_id _ = ent_decl' 
124       let signature = Entity entity_id args' res'
125       modA vsSignatures (Map.insert fname signature)
126       return ent_decl'
127   where
128     mkMap ::
129       --[(SignalId, SignalInfo)] 
130       CoreSyn.CoreBndr 
131       -> VHDLState VHDLSignalMapElement
132     -- We only need the vsTypes element from the state
133     mkMap = (\bndr ->
134       let
135         --info = Maybe.fromMaybe
136         --  (error $ "Signal not found in the name map? This should not happen!")
137         --  (lookup id sigmap)
138         --  Assume the bndr has a valid VHDL id already
139         id = bndrToVHDLId bndr
140         ty = Var.varType bndr
141       in
142         if True -- isPortSigUse $ sigUse info
143           then do
144             type_mark <- vhdl_ty ty
145             return $ Just (id, type_mark)
146           else
147             return $ Nothing
148        )
149
150   -- | Create the VHDL AST for an entity
151 createEntityAST ::
152   AST.VHDLId                   -- | The name of the function
153   -> [VHDLSignalMapElement]    -- | The entity's arguments
154   -> VHDLSignalMapElement      -- | The entity's result
155   -> AST.EntityDec             -- | The entity with the ent_decl filled in as well
156
157 createEntityAST vhdl_id args res =
158   AST.EntityDec vhdl_id ports
159   where
160     -- Create a basic Id, since VHDL doesn't grok filenames with extended Ids.
161     ports = Maybe.catMaybes $ 
162               map (mkIfaceSigDec AST.In) args
163               ++ [mkIfaceSigDec AST.Out res]
164               ++ [clk_port]
165     -- Add a clk port if we have state
166     clk_port = if True -- hasState hsfunc
167       then
168         Just $ AST.IfaceSigDec (mkVHDLExtId "clk") AST.In VHDL.std_logic_ty
169       else
170         Nothing
171
172 -- | Create a port declaration
173 mkIfaceSigDec ::
174   AST.Mode                         -- | The mode for the port (In / Out)
175   -> Maybe (AST.VHDLId, AST.TypeMark)    -- | The id and type for the port
176   -> Maybe AST.IfaceSigDec               -- | The resulting port declaration
177
178 mkIfaceSigDec mode (Just (id, ty)) = Just $ AST.IfaceSigDec id mode ty
179 mkIfaceSigDec _ Nothing = Nothing
180
181 -- | Generate a VHDL entity name for the given hsfunc
182 mkEntityId hsfunc =
183   -- TODO: This doesn't work for functions with multiple signatures!
184   -- Use a Basic Id, since using extended id's for entities throws off
185   -- precision and causes problems when generating filenames.
186   mkVHDLBasicId $ hsFuncName hsfunc
187
188 -- | Create an architecture for a given function
189 createArchitecture ::
190   (CoreSyn.CoreBndr, CoreSyn.CoreExpr) -- ^ The function
191   -> VHDLState AST.ArchBody -- ^ The architecture for this function
192
193 createArchitecture (fname, expr) = do
194   signaturemap <- getA vsSignatures
195   let signature = Maybe.fromMaybe 
196         (error $ "Generating architecture for function " ++ (pprString fname) ++ "without signature? This should not happen!")
197         (Map.lookup fname signaturemap)
198   let entity_id = ent_id signature
199   -- Strip off lambda's, these will be arguments
200   let (args, letexpr) = CoreSyn.collectBinders expr
201   -- There must be a let at top level 
202   let (CoreSyn.Let (CoreSyn.Rec binds) res) = letexpr
203
204   -- Create signal declarations for all internal and state signals
205   sig_dec_maybes <- mapM (mkSigDec' . fst) binds
206   let sig_decs = Maybe.catMaybes $ sig_dec_maybes
207
208   statements <- Monad.mapM mkConcSm binds
209   return $ AST.ArchBody (mkVHDLBasicId "structural") (AST.NSimple entity_id) (map AST.BDISD sig_decs) (statements ++ procs')
210   where
211     procs = map mkStateProcSm [] -- (makeStatePairs flatfunc)
212     procs' = map AST.CSPSm procs
213     -- mkSigDec only uses vsTypes from the state
214     mkSigDec' = mkSigDec
215
216 -- | Looks up all pairs of old state, new state signals, together with
217 --   the state id they represent.
218 makeStatePairs :: FlatFunction -> [(StateId, SignalInfo, SignalInfo)]
219 makeStatePairs flatfunc =
220   [(Maybe.fromJust $ oldStateId $ sigUse old_info, old_info, new_info) 
221     | old_info <- map snd (flat_sigs flatfunc)
222     , new_info <- map snd (flat_sigs flatfunc)
223         -- old_info must be an old state (and, because of the next equality,
224         -- new_info must be a new state).
225         , Maybe.isJust $ oldStateId $ sigUse old_info
226         -- And the state numbers must match
227     , (oldStateId $ sigUse old_info) == (newStateId $ sigUse new_info)]
228
229     -- Replace the second tuple element with the corresponding SignalInfo
230     --args_states = map (Arrow.second $ signalInfo sigs) args
231 mkStateProcSm :: (StateId, SignalInfo, SignalInfo) -> AST.ProcSm
232 mkStateProcSm (num, old, new) =
233   AST.ProcSm label [clk] [statement]
234   where
235     label       = mkVHDLExtId $ "state_" ++ (show num)
236     clk         = mkVHDLExtId "clk"
237     rising_edge = AST.NSimple $ mkVHDLBasicId "rising_edge"
238     wform       = AST.Wform [AST.WformElem (AST.PrimName $ AST.NSimple $ getSignalId new) Nothing]
239     assign      = AST.SigAssign (AST.NSimple $ getSignalId old) wform
240     rising_edge_clk = AST.PrimFCall $ AST.FCall rising_edge [Nothing AST.:=>: (AST.ADName $ AST.NSimple clk)]
241     statement   = AST.IfSm rising_edge_clk [assign] [] Nothing
242
243 mkSigDec :: CoreSyn.CoreBndr -> VHDLState (Maybe AST.SigDec)
244 mkSigDec bndr =
245   if True then do --isInternalSigUse use || isStateSigUse use then do
246     type_mark <- vhdl_ty $ Var.varType bndr
247     return $ Just (AST.SigDec (bndrToVHDLId bndr) type_mark Nothing)
248   else
249     return Nothing
250
251 -- | Creates a VHDL Id from a named SignalInfo. Errors out if the SignalInfo
252 --   is not named.
253 getSignalId :: SignalInfo -> AST.VHDLId
254 getSignalId info =
255     mkVHDLExtId $ Maybe.fromMaybe
256       (error $ "Unnamed signal? This should not happen!")
257       (sigName info)
258
259 -- | Transforms a core binding into a VHDL concurrent statement
260 mkConcSm ::
261   (CoreSyn.CoreBndr, CoreSyn.CoreExpr) -- ^ The binding to process
262   -> VHDLState AST.ConcSm  -- ^ The corresponding VHDL component instantiation.
263
264 mkConcSm (bndr, app@(CoreSyn.App _ _))= do
265   let (CoreSyn.Var f, args) = CoreSyn.collectArgs app
266   let valargs' = filter isValArg args
267   let valargs = filter (\(CoreSyn.Var bndr) -> not (Id.isDictId bndr)) valargs'
268   case Var.globalIdVarDetails f of
269     IdInfo.DataConWorkId dc ->
270         -- It's a datacon. Create a record from its arguments.
271         -- First, filter out type args. TODO: Is this the best way to do this?
272         -- The types should already have been taken into acocunt when creating
273         -- the signal, so this should probably work...
274         --let valargs = filter isValArg args in
275         if all is_var valargs then do
276           labels <- getFieldLabels (CoreUtils.exprType app)
277           let assigns = zipWith mkassign labels valargs
278           let block_id = bndrToVHDLId bndr
279           let block = AST.BlockSm block_id [] (AST.PMapAspect []) [] assigns
280           return $ AST.CSBSm block
281         else
282           error $ "VHDL.mkConcSm Not in normal form: One ore more complex arguments: " ++ pprString args
283       where
284         mkassign :: AST.VHDLId -> CoreExpr -> AST.ConcSm
285         mkassign label (Var arg) =
286           let sel_name = mkSelectedName bndr label in
287           mkUncondAssign (Right sel_name) (varToVHDLExpr arg)
288     IdInfo.VanillaGlobal -> do
289       -- It's a global value imported from elsewhere. These can be builtin
290       -- functions.
291       funSignatures <- getA vsNameTable
292       case (Map.lookup (bndrToString f) funSignatures) of
293         Just (arg_count, builder) ->
294           if length valargs == arg_count then
295             let
296               sigs = map (bndrToString.varBndr) valargs
297               sigsNames = map (\signal -> (AST.PrimName (AST.NSimple (mkVHDLExtId signal)))) sigs
298               func = builder sigsNames
299               src_wform = AST.Wform [AST.WformElem func Nothing]
300               dst_name = AST.NSimple (mkVHDLExtId (bndrToString bndr))
301               assign = dst_name AST.:<==: (AST.ConWforms [] src_wform Nothing)
302             in
303               return $ AST.CSSASm assign
304           else
305             error $ "VHDL.mkConcSm Incorrect number of arguments to builtin function: " ++ pprString f ++ " Args: " ++ pprString valargs
306         Nothing -> error $ "Using function from another module that is not a known builtin: " ++ pprString f
307     IdInfo.NotGlobalId -> do
308       signatures <- getA vsSignatures
309       -- This is a local id, so it should be a function whose definition we
310       -- have and which can be turned into a component instantiation.
311       let  
312         signature = Maybe.fromMaybe 
313           (error $ "Using function '" ++ (bndrToString f) ++ "' without signature? This should not happen!") 
314           (Map.lookup f signatures)
315         entity_id = ent_id signature
316         label = bndrToString bndr
317         -- Add a clk port if we have state
318         --clk_port = Maybe.fromJust $ mkAssocElem (Just $ mkVHDLExtId "clk") "clk"
319         --portmaps = mkAssocElems sigs args res signature ++ (if hasState hsfunc then [clk_port] else [])
320         portmaps = mkAssocElems args bndr signature
321         in
322           return $ AST.CSISm $ AST.CompInsSm (mkVHDLExtId label) (AST.IUEntity (AST.NSimple entity_id)) (AST.PMapAspect portmaps)
323     details -> error $ "Calling unsupported function " ++ pprString f ++ " with GlobalIdDetails " ++ pprString details
324
325 -- GHC generates some funny "r = r" bindings in let statements before
326 -- simplification. This outputs some dummy ConcSM for these, so things will at
327 -- least compile for now.
328 mkConcSm (bndr, CoreSyn.Var _) = return $ AST.CSPSm $ AST.ProcSm (mkVHDLBasicId "unused") [] []
329
330 -- A single alt case must be a selector. This means thee scrutinee is a simple
331 -- variable, the alternative is a dataalt with a single non-wild binder that
332 -- is also returned.
333 mkConcSm (bndr, expr@(Case (Var scrut) b ty [alt])) =
334   case alt of
335     (DataAlt dc, bndrs, (Var sel_bndr)) -> do
336       case List.elemIndex sel_bndr bndrs of
337         Just i -> do
338           labels <- getFieldLabels (Id.idType scrut)
339           let label = labels!!i
340           let sel_name = mkSelectedName scrut label
341           let sel_expr = AST.PrimName sel_name
342           return $ mkUncondAssign (Left bndr) sel_expr
343         Nothing -> error $ "VHDL.mkConcSM Not in normal form: Not a selector case:\n" ++ (pprString expr)
344       
345     _ -> error $ "VHDL.mkConcSM Not in normal form: Not a selector case:\n" ++ (pprString expr)
346
347 -- Multiple case alt are be conditional assignments and have only wild
348 -- binders in the alts and only variables in the case values and a variable
349 -- for a scrutinee. We check the constructor of the second alt, since the
350 -- first is the default case, if there is any.
351 mkConcSm (bndr, (Case (Var scrut) b ty [(_, _, Var false), (con, _, Var true)])) =
352   let
353     cond_expr = (varToVHDLExpr scrut) AST.:=: (conToVHDLExpr con)
354     true_expr  = (varToVHDLExpr true)
355     false_expr  = (varToVHDLExpr false)
356   in
357     return $ mkCondAssign (Left bndr) cond_expr true_expr false_expr
358 mkConcSm (_, (Case (Var _) _ _ alts)) = error "VHDL.mkConcSm Not in normal form: Case statement with more than two alternatives"
359 mkConcSm (_, Case _ _ _ _) = error "VHDL.mkConcSm Not in normal form: Case statement has does not have a simple variable as scrutinee"
360 mkConcSm (bndr, expr) = error $ "VHDL.mkConcSM Unsupported binding in let expression: " ++ pprString bndr ++ " = " ++ pprString expr
361
362 -- Create an unconditional assignment statement
363 mkUncondAssign ::
364   Either CoreBndr AST.VHDLName -- ^ The signal to assign to
365   -> AST.Expr -- ^ The expression to assign
366   -> AST.ConcSm -- ^ The resulting concurrent statement
367 mkUncondAssign dst expr = mkAssign dst Nothing expr
368
369 -- Create a conditional assignment statement
370 mkCondAssign ::
371   Either CoreBndr AST.VHDLName -- ^ The signal to assign to
372   -> AST.Expr -- ^ The condition
373   -> AST.Expr -- ^ The value when true
374   -> AST.Expr -- ^ The value when false
375   -> AST.ConcSm -- ^ The resulting concurrent statement
376 mkCondAssign dst cond true false = mkAssign dst (Just (cond, true)) false
377
378 -- Create a conditional or unconditional assignment statement
379 mkAssign ::
380   Either CoreBndr AST.VHDLName -> -- ^ The signal to assign to
381   Maybe (AST.Expr , AST.Expr) -> -- ^ Optionally, the condition to test for
382                                  -- and the value to assign when true.
383   AST.Expr -> -- ^ The value to assign when false or no condition
384   AST.ConcSm -- ^ The resulting concurrent statement
385
386 mkAssign dst cond false_expr =
387   let
388     -- I'm not 100% how this assignment AST works, but this gets us what we
389     -- want...
390     whenelse = case cond of
391       Just (cond_expr, true_expr) -> 
392         let 
393           true_wform = AST.Wform [AST.WformElem true_expr Nothing] 
394         in
395           [AST.WhenElse true_wform cond_expr]
396       Nothing -> []
397     false_wform = AST.Wform [AST.WformElem false_expr Nothing]
398     dst_name  = case dst of
399       Left bndr -> AST.NSimple (bndrToVHDLId bndr)
400       Right name -> name
401     assign    = dst_name AST.:<==: (AST.ConWforms whenelse false_wform Nothing)
402   in
403     AST.CSSASm assign
404
405 -- Create a record field selector that selects the given label from the record
406 -- stored in the given binder.
407 mkSelectedName :: CoreBndr -> AST.VHDLId -> AST.VHDLName
408 mkSelectedName bndr label =
409   let 
410     sel_prefix = AST.NSimple $ bndrToVHDLId bndr
411     sel_suffix = AST.SSimple $ label
412   in
413     AST.NSelected $ sel_prefix AST.:.: sel_suffix 
414
415 -- Finds the field labels for VHDL type generated for the given Core type,
416 -- which must result in a record type.
417 getFieldLabels :: Type.Type -> VHDLState [AST.VHDLId]
418 getFieldLabels ty = do
419   -- Ensure that the type is generated (but throw away it's VHDLId)
420   vhdl_ty ty
421   -- Get the types map, lookup and unpack the VHDL TypeDef
422   types <- getA vsTypes
423   case Map.lookup (OrdType ty) types of
424     Just (_, Left (AST.TDR (AST.RecordTypeDef elems))) -> return $ map (\(AST.ElementDec id _) -> id) elems
425     _ -> error $ "VHDL.getFieldLabels Type not found or not a record type? This should not happen! Type: " ++ (show ty)
426
427 -- Turn a variable reference into a AST expression
428 varToVHDLExpr :: Var.Var -> AST.Expr
429 varToVHDLExpr var = AST.PrimName $ AST.NSimple $ bndrToVHDLId var
430
431 -- Turn a constructor into an AST expression. For dataconstructors, this is
432 -- only the constructor itself, not any arguments it has. Should not be called
433 -- with a DEFAULT constructor.
434 conToVHDLExpr :: CoreSyn.AltCon -> AST.Expr
435 conToVHDLExpr (DataAlt dc) = AST.PrimLit lit
436   where
437     tycon = DataCon.dataConTyCon dc
438     tyname = TyCon.tyConName tycon
439     dcname = DataCon.dataConName dc
440     lit = case Name.getOccString tyname of
441       -- TODO: Do something more robust than string matching
442       "Bit"      -> case Name.getOccString dcname of "High" -> "'1'"; "Low" -> "'0'"
443       "Bool" -> case Name.getOccString dcname of "True" -> "true"; "False" -> "false"
444 conToVHDLExpr (LitAlt _) = error "VHDL.conToVHDLExpr Literals not support in case alternatives yet"
445 conToVHDLExpr DEFAULT = error "VHDL.conToVHDLExpr DEFAULT alternative should not occur here!"
446
447
448
449 {-
450 mkConcSm sigs (UncondDef src dst) _ = do
451   src_expr <- vhdl_expr src
452   let src_wform = AST.Wform [AST.WformElem src_expr Nothing]
453   let dst_name  = AST.NSimple (getSignalId $ signalInfo sigs dst)
454   let assign    = dst_name AST.:<==: (AST.ConWforms [] src_wform Nothing)
455   return $ AST.CSSASm assign
456   where
457     vhdl_expr (Left id) = return $ mkIdExpr sigs id
458     vhdl_expr (Right expr) =
459       case expr of
460         (EqLit id lit) ->
461           return $ (mkIdExpr sigs id) AST.:=: (AST.PrimLit lit)
462         (Literal lit Nothing) ->
463           return $ AST.PrimLit lit
464         (Literal lit (Just ty)) -> do
465           -- Create a cast expression, which is just a function call using the
466           -- type name as the function name.
467           let litexpr = AST.PrimLit lit
468           ty_id <- vhdl_ty ty
469           let ty_name = AST.NSimple ty_id
470           let args = [Nothing AST.:=>: (AST.ADExpr litexpr)] 
471           return $ AST.PrimFCall $ AST.FCall ty_name args
472         (Eq a b) ->
473          return $  (mkIdExpr sigs a) AST.:=: (mkIdExpr sigs b)
474
475 mkConcSm sigs (CondDef cond true false dst) _ =
476   let
477     cond_expr  = mkIdExpr sigs cond
478     true_expr  = mkIdExpr sigs true
479     false_expr  = mkIdExpr sigs false
480     false_wform = AST.Wform [AST.WformElem false_expr Nothing]
481     true_wform = AST.Wform [AST.WformElem true_expr Nothing]
482     whenelse = AST.WhenElse true_wform cond_expr
483     dst_name  = AST.NSimple (getSignalId $ signalInfo sigs dst)
484     assign    = dst_name AST.:<==: (AST.ConWforms [whenelse] false_wform Nothing)
485   in
486     return $ AST.CSSASm assign
487 -}
488 -- | Turn a SignalId into a VHDL Expr
489 mkIdExpr :: [(SignalId, SignalInfo)] -> SignalId -> AST.Expr
490 mkIdExpr sigs id =
491   let src_name  = AST.NSimple (getSignalId $ signalInfo sigs id) in
492   AST.PrimName src_name
493
494 mkAssocElems :: 
495   [CoreSyn.CoreExpr]            -- | The argument that are applied to function
496   -> CoreSyn.CoreBndr           -- | The binder in which to store the result
497   -> Entity                     -- | The entity to map against.
498   -> [AST.AssocElem]            -- | The resulting port maps
499
500 mkAssocElems args res entity =
501     -- Create the actual AssocElems
502     Maybe.catMaybes $ zipWith mkAssocElem ports sigs
503   where
504     -- Turn the ports and signals from a map into a flat list. This works,
505     -- since the maps must have an identical form by definition. TODO: Check
506     -- the similar form?
507     arg_ports = ent_args entity
508     res_port  = ent_res entity
509     -- Extract the id part from the (id, type) tuple
510     ports     = map (Monad.liftM fst) (res_port : arg_ports)
511     -- Translate signal numbers into names
512     sigs      = (bndrToString res : map (bndrToString.varBndr) args)
513
514 -- Turns a Var CoreExpr into the Id inside it. Will of course only work for
515 -- simple Var CoreExprs, not complexer ones.
516 varBndr :: CoreSyn.CoreExpr -> Var.Id
517 varBndr (CoreSyn.Var id) = id
518
519 -- | Look up a signal in the signal name map
520 lookupSigName :: [(SignalId, SignalInfo)] -> SignalId -> String
521 lookupSigName sigs sig = name
522   where
523     info = Maybe.fromMaybe
524       (error $ "Unknown signal " ++ (show sig) ++ " used? This should not happen!")
525       (lookup sig sigs)
526     name = Maybe.fromMaybe
527       (error $ "Unnamed signal " ++ (show sig) ++ " used? This should not happen!")
528       (sigName info)
529
530 -- | Create an VHDL port -> signal association
531 mkAssocElem :: Maybe AST.VHDLId -> String -> Maybe AST.AssocElem
532 mkAssocElem (Just port) signal = Just $ Just port AST.:=>: (AST.ADName (AST.NSimple (mkVHDLExtId signal))) 
533 mkAssocElem Nothing _ = Nothing
534
535 -- | The VHDL Bit type
536 bit_ty :: AST.TypeMark
537 bit_ty = AST.unsafeVHDLBasicId "Bit"
538
539 -- | The VHDL Boolean type
540 bool_ty :: AST.TypeMark
541 bool_ty = AST.unsafeVHDLBasicId "Boolean"
542
543 -- | The VHDL std_logic
544 std_logic_ty :: AST.TypeMark
545 std_logic_ty = AST.unsafeVHDLBasicId "std_logic"
546
547 -- Translate a Haskell type to a VHDL type
548 vhdl_ty :: Type.Type -> VHDLState AST.TypeMark
549 vhdl_ty ty = do
550   typemap <- getA vsTypes
551   let builtin_ty = do -- See if this is a tycon and lookup its name
552         (tycon, args) <- Type.splitTyConApp_maybe ty
553         let name = Name.getOccString (TyCon.tyConName tycon)
554         Map.lookup name builtin_types
555   -- If not a builtin type, try the custom types
556   let existing_ty = (fmap fst) $ Map.lookup (OrdType ty) typemap
557   case Monoid.getFirst $ Monoid.mconcat (map Monoid.First [builtin_ty, existing_ty]) of
558     -- Found a type, return it
559     Just t -> return t
560     -- No type yet, try to construct it
561     Nothing -> do
562       newty_maybe <- (construct_vhdl_ty ty)
563       case newty_maybe of
564         Just (ty_id, ty_def) -> do
565           -- TODO: Check name uniqueness
566           modA vsTypes (Map.insert (OrdType ty) (ty_id, ty_def))
567           return ty_id
568         Nothing -> error $ "Unsupported Haskell type: " ++ (showSDoc $ ppr ty)
569
570 -- Construct a new VHDL type for the given Haskell type.
571 construct_vhdl_ty :: Type.Type -> VHDLState (Maybe (AST.TypeMark, Either AST.TypeDef AST.SubtypeIn))
572 construct_vhdl_ty ty = do
573   case Type.splitTyConApp_maybe ty of
574     Just (tycon, args) -> do
575       let name = Name.getOccString (TyCon.tyConName tycon)
576       case name of
577         "TFVec" -> do
578           res <- mk_vector_ty (tfvec_len ty) (tfvec_elem ty)
579           return $ Just $ (Arrow.second Right) res
580         -- "SizedWord" -> do
581         --   res <- mk_vector_ty (sized_word_len ty) ty
582         --   return $ Just $ (Arrow.second Left) res
583         "RangedWord" -> do 
584           res <- mk_natural_ty 0 (ranged_word_bound ty)
585           return $ Just $ (Arrow.second Right) res
586         -- Create a custom type from this tycon
587         otherwise -> mk_tycon_ty tycon args
588     Nothing -> return $ Nothing
589
590 -- | Create VHDL type for a custom tycon
591 mk_tycon_ty :: TyCon.TyCon -> [Type.Type] -> VHDLState (Maybe (AST.TypeMark, Either AST.TypeDef AST.SubtypeIn))
592 mk_tycon_ty tycon args =
593   case TyCon.tyConDataCons tycon of
594     -- Not an algebraic type
595     [] -> error $ "Only custom algebraic types are supported: " ++  (showSDoc $ ppr tycon)
596     [dc] -> do
597       let arg_tys = DataCon.dataConRepArgTys dc
598       -- TODO: CoreSubst docs say each Subs can be applied only once. Is this a
599       -- violation? Or does it only mean not to apply it again to the same
600       -- subject?
601       let real_arg_tys = map (CoreSubst.substTy subst) arg_tys
602       elem_tys <- mapM vhdl_ty real_arg_tys
603       let elems = zipWith AST.ElementDec recordlabels elem_tys
604       -- For a single construct datatype, build a record with one field for
605       -- each argument.
606       -- TODO: Add argument type ids to this, to ensure uniqueness
607       -- TODO: Special handling for tuples?
608       let ty_id = mkVHDLExtId $ nameToString (TyCon.tyConName tycon)
609       let ty_def = AST.TDR $ AST.RecordTypeDef elems
610       return $ Just (ty_id, Left ty_def)
611     dcs -> error $ "Only single constructor datatypes supported: " ++  (showSDoc $ ppr tycon)
612   where
613     -- Create a subst that instantiates all types passed to the tycon
614     -- TODO: I'm not 100% sure that this is the right way to do this. It seems
615     -- to work so far, though..
616     tyvars = TyCon.tyConTyVars tycon
617     subst = CoreSubst.extendTvSubstList CoreSubst.emptySubst (zip tyvars args)
618
619 -- | Create a VHDL vector type
620 mk_vector_ty ::
621   Int -- ^ The length of the vector
622   -> Type.Type -- ^ The Haskell element type of the Vector
623   -> VHDLState (AST.TypeMark, AST.SubtypeIn) -- The typemark created.
624
625 mk_vector_ty len el_ty = do
626   elem_types_map <- getA vsElemTypes
627   el_ty_tm <- vhdl_ty el_ty
628   let ty_id = mkVHDLExtId $ "vector-"++ (AST.fromVHDLId el_ty_tm) ++ "-0_to_" ++ (show len)
629   let range = AST.ConstraintIndex $ AST.IndexConstraint [AST.ToRange (AST.PrimLit "0") (AST.PrimLit $ show (len - 1))]
630   let existing_elem_ty = (fmap fst) $ Map.lookup (OrdType el_ty) elem_types_map
631   case existing_elem_ty of
632     Just t -> do
633       let ty_def = AST.SubtypeIn t (Just range)
634       return (ty_id, ty_def)
635     Nothing -> do
636       let vec_id = mkVHDLExtId $ "vector_" ++ (AST.fromVHDLId el_ty_tm)
637       let vec_def = AST.TDA $ AST.UnconsArrayDef [tfvec_indexTM] el_ty_tm
638       modA vsElemTypes (Map.insert (OrdType el_ty) (vec_id, vec_def))
639       modA vsTypeFuns (Map.insert (OrdType el_ty) (genUnconsVectorFuns el_ty_tm vec_id)) 
640       let ty_def = AST.SubtypeIn vec_id (Just range)
641       return (ty_id, ty_def)
642
643 mk_natural_ty ::
644   Int -- ^ The minimum bound (> 0)
645   -> Int -- ^ The maximum bound (> minimum bound)
646   -> VHDLState (AST.TypeMark, AST.SubtypeIn) -- The typemark created.
647 mk_natural_ty min_bound max_bound = do
648   let ty_id = mkVHDLExtId $ "nat_" ++ (show min_bound) ++ "_to_" ++ (show max_bound)
649   let range = AST.ConstraintRange $ AST.SubTypeRange (AST.PrimLit $ (show min_bound)) (AST.PrimLit $ (show max_bound))
650   let ty_def = AST.SubtypeIn naturalTM (Just range)
651   return (ty_id, ty_def)
652   
653 builtin_types = 
654   Map.fromList [
655     ("Bit", std_logic_ty),
656     ("Bool", bool_ty) -- TysWiredIn.boolTy
657   ]
658
659 -- Shortcut for 
660 -- Can only contain alphanumerics and underscores. The supplied string must be
661 -- a valid basic id, otherwise an error value is returned. This function is
662 -- not meant to be passed identifiers from a source file, use mkVHDLExtId for
663 -- that.
664 mkVHDLBasicId :: String -> AST.VHDLId
665 mkVHDLBasicId s = 
666   AST.unsafeVHDLBasicId $ (strip_multiscore . strip_leading . strip_invalid) s
667   where
668     -- Strip invalid characters.
669     strip_invalid = filter (`elem` ['A'..'Z'] ++ ['a'..'z'] ++ ['0'..'9'] ++ "_.")
670     -- Strip leading numbers and underscores
671     strip_leading = dropWhile (`elem` ['0'..'9'] ++ "_")
672     -- Strip multiple adjacent underscores
673     strip_multiscore = concat . map (\cs -> 
674         case cs of 
675           ('_':_) -> "_"
676           _ -> cs
677       ) . List.group
678
679 -- Shortcut for Extended VHDL Id's. These Id's can contain a lot more
680 -- different characters than basic ids, but can never be used to refer to
681 -- basic ids.
682 -- Use extended Ids for any values that are taken from the source file.
683 mkVHDLExtId :: String -> AST.VHDLId
684 mkVHDLExtId s = 
685   AST.unsafeVHDLExtId $ strip_invalid s
686   where 
687     -- Allowed characters, taken from ForSyde's mkVHDLExtId
688     allowed = ['A'..'Z'] ++ ['a'..'z'] ++ ['0'..'9'] ++ " \"#&\\'()*+,./:;<=>_|!$%@?[]^`{}~-"
689     strip_invalid = filter (`elem` allowed)
690
691 -- Creates a VHDL Id from a binder
692 bndrToVHDLId ::
693   CoreSyn.CoreBndr
694   -> AST.VHDLId
695
696 bndrToVHDLId = mkVHDLExtId . OccName.occNameString . Name.nameOccName . Var.varName
697
698 -- Extracts the binder name as a String
699 bndrToString ::
700   CoreSyn.CoreBndr
701   -> String
702 bndrToString = OccName.occNameString . Name.nameOccName . Var.varName
703
704 -- Get the string version a Var's unique
705 varToStringUniq = show . Var.varUnique
706
707 -- Extracts the string version of the name
708 nameToString :: Name.Name -> String
709 nameToString = OccName.occNameString . Name.nameOccName
710
711 recordlabels = map (\c -> mkVHDLBasicId [c]) ['A'..'Z']
712
713 -- | Map a port specification of a builtin function to a VHDL Signal to put in
714 --   a VHDLSignalMap
715 toVHDLSignalMapElement :: (String, AST.TypeMark) -> VHDLSignalMapElement
716 toVHDLSignalMapElement (name, ty) = Just (mkVHDLBasicId name, ty)