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