Make modFuncs work with stateful functions.
[matthijs/master-project/cλash.git] / VHDL.hs
1 --
2 -- Functions to generate VHDL from FlatFunctions
3 --
4 module VHDL where
5
6 import Data.Traversable
7 import qualified Data.Foldable as Foldable
8 import qualified Maybe
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
21 -- | Create an entity for a given function
22 createEntity ::
23   HsFunction        -- | The function signature
24   -> FuncData       -- | The function data collected so far
25   -> VHDLState ()
26
27 createEntity hsfunc fdata = 
28   let func = flatFunc fdata in
29   case func of
30     -- Skip (builtin) functions without a FlatFunction
31     Nothing -> do return ()
32     -- Create an entity for all other functions
33     Just flatfunc ->
34       
35       let 
36         sigs    = flat_sigs flatfunc
37         args    = flat_args flatfunc
38         res     = flat_res  flatfunc
39         args'   = map (fmap (mkMap sigs)) args
40         res'    = fmap (mkMap sigs) res
41         ent_decl' = createEntityAST hsfunc args' res'
42         entity' = Entity args' res' (Just ent_decl')
43       in
44         setEntity hsfunc entity'
45   where
46     mkMap :: Eq id => [(id, SignalInfo)] -> id -> (AST.VHDLId, AST.TypeMark)
47     mkMap sigmap id =
48       (mkVHDLId nm, vhdl_ty ty)
49       where
50         info = Maybe.fromMaybe
51           (error $ "Signal not found in the name map? This should not happen!")
52           (lookup id sigmap)
53         nm = Maybe.fromMaybe
54           (error $ "Signal not named? This should not happen!")
55           (sigName info)
56         ty = sigTy info
57
58 -- | Create the VHDL AST for an entity
59 createEntityAST ::
60   HsFunction            -- | The signature of the function we're working with
61   -> [VHDLSignalMap]    -- | The entity's arguments
62   -> VHDLSignalMap      -- | The entity's result
63   -> AST.EntityDec      -- | The entity with the ent_decl filled in as well
64
65 createEntityAST hsfunc args res =
66   AST.EntityDec vhdl_id ports
67   where
68     vhdl_id = mkEntityId hsfunc
69     ports = concatMap (mapToPorts AST.In) args
70             ++ mapToPorts AST.Out res
71     mapToPorts :: AST.Mode -> VHDLSignalMap -> [AST.IfaceSigDec] 
72     mapToPorts mode m =
73       map (mkIfaceSigDec mode) (Foldable.toList m)
74
75 -- | Create a port declaration
76 mkIfaceSigDec ::
77   AST.Mode                         -- | The mode for the port (In / Out)
78   -> (AST.VHDLId, AST.TypeMark)    -- | The id and type for the port
79   -> AST.IfaceSigDec               -- | The resulting port declaration
80
81 mkIfaceSigDec mode (id, ty) = AST.IfaceSigDec id mode ty
82
83 -- | Generate a VHDL entity name for the given hsfunc
84 mkEntityId hsfunc =
85   -- TODO: This doesn't work for functions with multiple signatures!
86   mkVHDLId $ hsFuncName hsfunc
87
88 -- | Create an architecture for a given function
89 createArchitecture ::
90   HsFunction        -- | The function signature
91   -> FuncData       -- | The function data collected so far
92   -> VHDLState ()
93
94 createArchitecture hsfunc fdata = 
95   let func = flatFunc fdata in
96   case func of
97     -- Skip (builtin) functions without a FlatFunction
98     Nothing -> do return ()
99     -- Create an architecture for all other functions
100     Just flatfunc ->
101       let 
102         sigs      = flat_sigs flatfunc
103         args      = flat_args flatfunc
104         res       = flat_res  flatfunc
105         apps      = flat_apps flatfunc
106         entity_id = Maybe.fromMaybe
107                       (error $ "Building architecture without an entity? This should not happen!")
108                       (getEntityId fdata)
109         -- Create signal declarations for all signals that are not in args and
110         -- res
111         sig_decs = [mkSigDec info | (id, info) <- sigs, (all (id `Foldable.notElem`) (res:args)) ]
112         -- Create component instantiations for all function applications
113         insts    = map (AST.CSISm . mkCompInsSm) apps
114         arch     = AST.ArchBody (mkVHDLId "structural") (AST.NSimple entity_id) (map AST.BDISD sig_decs) insts
115       in
116         setArchitecture hsfunc arch
117
118 mkSigDec :: SignalInfo -> AST.SigDec
119 mkSigDec info =
120     AST.SigDec (mkVHDLId name) (vhdl_ty ty) Nothing
121   where
122     name = Maybe.fromMaybe
123       (error $ "Unnamed signal? This should not happen!")
124       (sigName info)
125     ty = sigTy info
126
127 -- | Transforms a flat function application to a VHDL component instantiation.
128 mkCompInsSm ::
129   FApp UnnamedSignal  -- | The application to look at.
130   -> AST.CompInsSm    -- | The corresponding VHDL component instantiation.
131
132 mkCompInsSm app =
133   AST.CompInsSm label (AST.IUEntity (AST.NSimple entity_id)) (AST.PMapAspect portmaps)
134   where
135     entity_id = mkVHDLId "foo"
136     label     = mkVHDLId "app"
137     portmaps  = []
138
139 -- | Extracts the generated entity id from the given funcdata
140 getEntityId :: FuncData -> Maybe AST.VHDLId
141 getEntityId fdata =
142   case funcEntity fdata of
143     Nothing -> Nothing
144     Just e  -> case ent_decl e of
145       Nothing -> Nothing
146       Just (AST.EntityDec id _) -> Just id
147
148 getLibraryUnits ::
149   (HsFunction, FuncData)      -- | A function from the session
150   -> [AST.LibraryUnit]        -- | The library units it generates
151
152 getLibraryUnits (hsfunc, fdata) =
153   case funcEntity fdata of 
154     Nothing -> []
155     Just ent -> case ent_decl ent of
156       Nothing -> []
157       Just decl -> [AST.LUEntity decl]
158   ++
159   case funcArch fdata of
160     Nothing -> []
161     Just arch -> [AST.LUArch arch]
162
163 -- | The VHDL Bit type
164 bit_ty :: AST.TypeMark
165 bit_ty = AST.unsafeVHDLBasicId "Bit"
166
167 -- Translate a Haskell type to a VHDL type
168 vhdl_ty :: Type.Type -> AST.TypeMark
169 vhdl_ty ty = Maybe.fromMaybe
170   (error $ "Unsupported Haskell type: " ++ (showSDoc $ ppr ty))
171   (vhdl_ty_maybe ty)
172
173 -- Translate a Haskell type to a VHDL type
174 vhdl_ty_maybe :: Type.Type -> Maybe AST.TypeMark
175 vhdl_ty_maybe ty =
176   case Type.splitTyConApp_maybe ty of
177     Just (tycon, args) ->
178       let name = TyCon.tyConName tycon in
179         -- TODO: Do something more robust than string matching
180         case Name.getOccString name of
181           "Bit"      -> Just bit_ty
182           otherwise  -> Nothing
183     otherwise -> Nothing
184
185 -- Shortcut
186 mkVHDLId :: String -> AST.VHDLId
187 mkVHDLId = AST.unsafeVHDLBasicId