Enable the DontCare value for Bit again.
[matthijs/master-project/cλash.git] / VHDL.hs
1 --
2 -- Functions to generate VHDL from FlatFunctions
3 --
4 module VHDL where
5
6 import qualified Data.Foldable as Foldable
7 import qualified Maybe
8 import qualified Control.Monad as Monad
9
10 import qualified Type
11 import qualified TysWiredIn
12 import qualified Name
13 import qualified TyCon
14 import Outputable ( showSDoc, ppr )
15
16 import qualified ForSyDe.Backend.VHDL.AST as AST
17
18 import VHDLTypes
19 import Flatten
20 import FlattenTypes
21 import TranslatorTypes
22 import Pretty
23
24 getDesignFile :: VHDLState AST.DesignFile
25 getDesignFile = do
26   -- Extract the library units generated from all the functions in the
27   -- session.
28   funcs <- getFuncs
29   let units = concat $ map getLibraryUnits funcs
30   let context = [
31         AST.Library $ mkVHDLId "IEEE",
32         AST.Use $ (AST.NSimple $ mkVHDLId "IEEE.std_logic_1164") AST.:.: AST.All]
33   return $ AST.DesignFile 
34     context
35     units
36   
37 -- | Create an entity for a given function
38 createEntity ::
39   HsFunction        -- | The function signature
40   -> FuncData       -- | The function data collected so far
41   -> VHDLState ()
42
43 createEntity hsfunc fdata = 
44   let func = flatFunc fdata in
45   case func of
46     -- Skip (builtin) functions without a FlatFunction
47     Nothing -> do return ()
48     -- Create an entity for all other functions
49     Just flatfunc ->
50       
51       let 
52         sigs    = flat_sigs flatfunc
53         args    = flat_args flatfunc
54         res     = flat_res  flatfunc
55         args'   = map (fmap (mkMap sigs)) args
56         res'    = fmap (mkMap sigs) res
57         ent_decl' = createEntityAST hsfunc args' res'
58         AST.EntityDec entity_id _ = ent_decl' 
59         entity' = Entity entity_id args' res' (Just ent_decl')
60       in
61         setEntity hsfunc entity'
62   where
63     mkMap :: Eq id => [(id, SignalInfo)] -> id -> Maybe (AST.VHDLId, AST.TypeMark)
64     mkMap sigmap id =
65       if isPortSigUse $ sigUse info
66         then
67           Just (mkVHDLId nm, vhdl_ty ty)
68         else
69           Nothing
70       where
71         info = Maybe.fromMaybe
72           (error $ "Signal not found in the name map? This should not happen!")
73           (lookup id sigmap)
74         nm = Maybe.fromMaybe
75           (error $ "Signal not named? This should not happen!")
76           (sigName info)
77         ty = sigTy info
78
79   -- | Create the VHDL AST for an entity
80 createEntityAST ::
81   HsFunction            -- | The signature of the function we're working with
82   -> [VHDLSignalMap]    -- | The entity's arguments
83   -> VHDLSignalMap      -- | The entity's result
84   -> AST.EntityDec      -- | The entity with the ent_decl filled in as well
85
86 createEntityAST hsfunc args res =
87   AST.EntityDec vhdl_id ports
88   where
89     vhdl_id = mkEntityId hsfunc
90     ports = concatMap (mapToPorts AST.In) args
91             ++ mapToPorts AST.Out res
92             ++ clk_port
93     mapToPorts :: AST.Mode -> VHDLSignalMap -> [AST.IfaceSigDec] 
94     mapToPorts mode m =
95       Maybe.catMaybes $ map (mkIfaceSigDec mode) (Foldable.toList m)
96     -- Add a clk port if we have state
97     clk_port = if hasState hsfunc
98       then
99         [AST.IfaceSigDec (mkVHDLId "clk") AST.In VHDL.std_logic_ty]
100       else
101         []
102
103 -- | Create a port declaration
104 mkIfaceSigDec ::
105   AST.Mode                         -- | The mode for the port (In / Out)
106   -> Maybe (AST.VHDLId, AST.TypeMark)    -- | The id and type for the port
107   -> Maybe AST.IfaceSigDec               -- | The resulting port declaration
108
109 mkIfaceSigDec mode (Just (id, ty)) = Just $ AST.IfaceSigDec id mode ty
110 mkIfaceSigDec _ Nothing = Nothing
111
112 -- | Generate a VHDL entity name for the given hsfunc
113 mkEntityId hsfunc =
114   -- TODO: This doesn't work for functions with multiple signatures!
115   mkVHDLId $ hsFuncName hsfunc
116
117 -- | Create an architecture for a given function
118 createArchitecture ::
119   HsFunction        -- | The function signature
120   -> FuncData       -- | The function data collected so far
121   -> VHDLState ()
122
123 createArchitecture hsfunc fdata = 
124   let func = flatFunc fdata in
125   case func of
126     -- Skip (builtin) functions without a FlatFunction
127     Nothing -> do return ()
128     -- Create an architecture for all other functions
129     Just flatfunc -> do
130       let sigs = flat_sigs flatfunc
131       let args = flat_args flatfunc
132       let res  = flat_res  flatfunc
133       let defs = flat_defs flatfunc
134       let entity_id = Maybe.fromMaybe
135                       (error $ "Building architecture without an entity? This should not happen!")
136                       (getEntityId fdata)
137       -- Create signal declarations for all signals that are not in args and
138       -- res
139       let sig_decs = Maybe.catMaybes $ map (mkSigDec . snd) sigs
140       -- Create concurrent statements for all signal definitions
141       statements <- mapM (mkConcSm sigs) defs
142       let procs = map mkStateProcSm (getOwnStates hsfunc flatfunc)
143       let procs' = map AST.CSPSm procs
144       let arch = AST.ArchBody (mkVHDLId "structural") (AST.NSimple entity_id) (map AST.BDISD sig_decs) (statements ++ procs')
145       setArchitecture hsfunc arch
146
147 mkStateProcSm :: (StateId, SignalInfo, SignalInfo) -> AST.ProcSm
148 mkStateProcSm (num, old, new) =
149   AST.ProcSm label [clk] [statement]
150   where
151     label       = mkVHDLId $ "state_" ++ (show num)
152     clk         = mkVHDLId "clk"
153     rising_edge = AST.NSimple $ mkVHDLId "rising_edge"
154     wform       = AST.Wform [AST.WformElem (AST.PrimName $ AST.NSimple $ getSignalId new) Nothing]
155     assign      = AST.SigAssign (AST.NSimple $ getSignalId old) wform
156     rising_edge_clk = AST.PrimFCall $ AST.FCall rising_edge [Nothing AST.:=>: (AST.ADName $ AST.NSimple clk)]
157     statement   = AST.IfSm rising_edge_clk [assign] [] Nothing
158
159 mkSigDec :: SignalInfo -> Maybe AST.SigDec
160 mkSigDec info =
161   let use = sigUse info in
162   if isInternalSigUse use || isStateSigUse use then
163     Just $ AST.SigDec (getSignalId info) (vhdl_ty ty) Nothing
164   else
165     Nothing
166   where
167     ty = sigTy info
168
169 -- | Creates a VHDL Id from a named SignalInfo. Errors out if the SignalInfo
170 --   is not named.
171 getSignalId :: SignalInfo -> AST.VHDLId
172 getSignalId info =
173     mkVHDLId $ Maybe.fromMaybe
174       (error $ "Unnamed signal? This should not happen!")
175       (sigName info)
176
177 -- | Transforms a signal definition into a VHDL concurrent statement
178 mkConcSm ::
179   [(SignalId, SignalInfo)] -- | The signals in the current architecture
180   -> SigDef                -- | The signal definition
181   -> VHDLState AST.ConcSm    -- | The corresponding VHDL component instantiation.
182
183 mkConcSm sigs (FApp hsfunc args res) = do
184   fdata_maybe <- getFunc hsfunc
185   let fdata = Maybe.fromMaybe
186         (error $ "Using function '" ++ (prettyShow hsfunc) ++ "' that is not in the session? This should not happen!")
187         fdata_maybe
188   let entity = Maybe.fromMaybe
189         (error $ "Using function '" ++ (prettyShow hsfunc) ++ "' without entity declaration? This should not happen!")
190         (funcEntity fdata)
191   let entity_id = ent_id entity
192   label <- uniqueName (AST.fromVHDLId entity_id)
193   let portmaps = mkAssocElems sigs args res entity
194   return $ AST.CSISm $ AST.CompInsSm (mkVHDLId label) (AST.IUEntity (AST.NSimple entity_id)) (AST.PMapAspect portmaps)
195
196 mkConcSm sigs (UncondDef src dst) = do
197   let src_expr  = vhdl_expr src
198   let src_wform = AST.Wform [AST.WformElem src_expr Nothing]
199   let dst_name  = AST.NSimple (getSignalId $ signalInfo sigs dst)
200   let assign    = dst_name AST.:<==: (AST.ConWforms [] src_wform Nothing)
201   return $ AST.CSSASm assign
202   where
203     vhdl_expr (Left id) = mkIdExpr sigs id
204     vhdl_expr (Right expr) =
205       case expr of
206         (EqLit id lit) ->
207           (mkIdExpr sigs id) AST.:=: (AST.PrimLit lit)
208         (Literal lit) ->
209           AST.PrimLit lit
210         (Eq a b) ->
211           (mkIdExpr sigs a) AST.:=: (mkIdExpr sigs b)
212
213 mkConcSm sigs (CondDef cond true false dst) = do
214   let cond_expr  = mkIdExpr sigs cond
215   let true_expr  = mkIdExpr sigs true
216   let false_expr  = mkIdExpr sigs false
217   let false_wform = AST.Wform [AST.WformElem false_expr Nothing]
218   let true_wform = AST.Wform [AST.WformElem true_expr Nothing]
219   let whenelse = AST.WhenElse true_wform cond_expr
220   let dst_name  = AST.NSimple (getSignalId $ signalInfo sigs dst)
221   let assign    = dst_name AST.:<==: (AST.ConWforms [whenelse] false_wform Nothing)
222   return $ AST.CSSASm assign
223
224 -- | Turn a SignalId into a VHDL Expr
225 mkIdExpr :: [(SignalId, SignalInfo)] -> SignalId -> AST.Expr
226 mkIdExpr sigs id =
227   let src_name  = AST.NSimple (getSignalId $ signalInfo sigs id) in
228   AST.PrimName src_name
229
230 mkAssocElems :: 
231   [(SignalId, SignalInfo)]      -- | The signals in the current architecture
232   -> [SignalMap]                -- | The signals that are applied to function
233   -> SignalMap                  -- | the signals in which to store the function result
234   -> Entity                     -- | The entity to map against.
235   -> [AST.AssocElem]            -- | The resulting port maps
236
237 mkAssocElems sigmap args res entity =
238     -- Create the actual AssocElems
239     Maybe.catMaybes $ zipWith mkAssocElem ports sigs
240   where
241     -- Turn the ports and signals from a map into a flat list. This works,
242     -- since the maps must have an identical form by definition. TODO: Check
243     -- the similar form?
244     arg_ports = concat (map Foldable.toList (ent_args entity))
245     res_ports = Foldable.toList (ent_res entity)
246     arg_sigs  = (concat (map Foldable.toList args))
247     res_sigs  = Foldable.toList res
248     -- Extract the id part from the (id, type) tuple
249     ports     = (map (fmap fst) (arg_ports ++ res_ports)) 
250     -- Translate signal numbers into names
251     sigs      = (map (lookupSigName sigmap) (arg_sigs ++ res_sigs))
252
253 -- | Look up a signal in the signal name map
254 lookupSigName :: [(SignalId, SignalInfo)] -> SignalId -> String
255 lookupSigName sigs sig = name
256   where
257     info = Maybe.fromMaybe
258       (error $ "Unknown signal " ++ (show sig) ++ " used? This should not happen!")
259       (lookup sig sigs)
260     name = Maybe.fromMaybe
261       (error $ "Unnamed signal " ++ (show sig) ++ " used? This should not happen!")
262       (sigName info)
263
264 -- | Create an VHDL port -> signal association
265 mkAssocElem :: Maybe AST.VHDLId -> String -> Maybe AST.AssocElem
266 mkAssocElem (Just port) signal = Just $ Just port AST.:=>: (AST.ADName (AST.NSimple (mkVHDLId signal))) 
267 mkAssocElem Nothing _ = Nothing
268
269 -- | Extracts the generated entity id from the given funcdata
270 getEntityId :: FuncData -> Maybe AST.VHDLId
271 getEntityId fdata =
272   case funcEntity fdata of
273     Nothing -> Nothing
274     Just e  -> case ent_decl e of
275       Nothing -> Nothing
276       Just (AST.EntityDec id _) -> Just id
277
278 getLibraryUnits ::
279   (HsFunction, FuncData)      -- | A function from the session
280   -> [AST.LibraryUnit]        -- | The library units it generates
281
282 getLibraryUnits (hsfunc, fdata) =
283   case funcEntity fdata of 
284     Nothing -> []
285     Just ent -> case ent_decl ent of
286       Nothing -> []
287       Just decl -> [AST.LUEntity decl]
288   ++
289   case funcArch fdata of
290     Nothing -> []
291     Just arch -> [AST.LUArch arch]
292
293 -- | The VHDL Bit type
294 bit_ty :: AST.TypeMark
295 bit_ty = AST.unsafeVHDLBasicId "Bit"
296
297 -- | The VHDL Boolean type
298 bool_ty :: AST.TypeMark
299 bool_ty = AST.unsafeVHDLBasicId "Boolean"
300
301 -- | The VHDL std_logic
302 std_logic_ty :: AST.TypeMark
303 std_logic_ty = AST.unsafeVHDLBasicId "std_logic"
304
305 -- Translate a Haskell type to a VHDL type
306 vhdl_ty :: Type.Type -> AST.TypeMark
307 vhdl_ty ty = Maybe.fromMaybe
308   (error $ "Unsupported Haskell type: " ++ (showSDoc $ ppr ty))
309   (vhdl_ty_maybe ty)
310
311 -- Translate a Haskell type to a VHDL type
312 vhdl_ty_maybe :: Type.Type -> Maybe AST.TypeMark
313 vhdl_ty_maybe ty =
314   if Type.coreEqType ty TysWiredIn.boolTy
315     then
316       Just bool_ty
317     else
318       case Type.splitTyConApp_maybe ty of
319         Just (tycon, args) ->
320           let name = TyCon.tyConName tycon in
321             -- TODO: Do something more robust than string matching
322             case Name.getOccString name of
323               "Bit"      -> Just std_logic_ty
324               otherwise  -> Nothing
325         otherwise -> Nothing
326
327 -- Shortcut
328 mkVHDLId :: String -> AST.VHDLId
329 mkVHDLId = AST.unsafeVHDLBasicId