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