9cea6fe74c333910ef8fd1b9919d61e8e5f9694f
[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   -> FuncData       -- | The modified function data
26
27 createEntity hsfunc fdata = 
28   let func = flatFunc fdata in
29   case func of
30     -- Skip (builtin) functions without a FlatFunction
31     Nothing -> fdata
32     -- Create an entity for all other functions
33     Just flatfunc ->
34       
35       let 
36         s       = sigs flatfunc
37         a       = args flatfunc
38         r       = res  flatfunc
39         args'   = map (fmap (mkMap s)) a
40         res'    = fmap (mkMap s) r
41         ent_decl' = createEntityAST hsfunc args' res'
42         entity' = Entity args' res' (Just ent_decl')
43       in
44         fdata { entity = Just 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   -> FuncData       -- | The modified function data
93
94 createArchitecture hsfunc fdata = 
95   let func = flatFunc fdata in
96   case func of
97     -- Skip (builtin) functions without a FlatFunction
98     Nothing -> fdata
99     -- Create an architecture for all other functions
100     Just flatfunc ->
101       let 
102         s        = sigs flatfunc
103         a        = args flatfunc
104         r        = res  flatfunc
105         entity_id = Maybe.fromMaybe
106                       (error $ "Building architecture without an entity? This should not happen!")
107                       (getEntityId fdata)
108         sig_decs = [mkSigDec info | (id, info) <- s, (all (id `Foldable.notElem`) (r:a)) ]
109         arch     = AST.ArchBody (mkVHDLId "structural") (AST.NSimple entity_id) (map AST.BDISD sig_decs) []
110       in
111         fdata { funcArch = Just arch }
112
113 mkSigDec :: SignalInfo -> AST.SigDec
114 mkSigDec info =
115     AST.SigDec (mkVHDLId name) (vhdl_ty ty) Nothing
116   where
117     name = Maybe.fromMaybe
118       (error $ "Unnamed signal? This should not happen!")
119       (sigName info)
120     ty = sigTy info
121     
122 -- | Extracts the generated entity id from the given funcdata
123 getEntityId :: FuncData -> Maybe AST.VHDLId
124 getEntityId fdata =
125   case entity fdata of
126     Nothing -> Nothing
127     Just e  -> case ent_decl e of
128       Nothing -> Nothing
129       Just (AST.EntityDec id _) -> Just id
130
131 getLibraryUnits ::
132   (HsFunction, FuncData)      -- | A function from the session
133   -> [AST.LibraryUnit]        -- | The library units it generates
134
135 getLibraryUnits (hsfunc, fdata) =
136   case entity fdata of 
137     Nothing -> []
138     Just ent -> case ent_decl ent of
139       Nothing -> []
140       Just decl -> [AST.LUEntity decl]
141   ++
142   case funcArch fdata of
143     Nothing -> []
144     Just arch -> [AST.LUArch arch]
145
146 -- | The VHDL Bit type
147 bit_ty :: AST.TypeMark
148 bit_ty = AST.unsafeVHDLBasicId "Bit"
149
150 -- Translate a Haskell type to a VHDL type
151 vhdl_ty :: Type.Type -> AST.TypeMark
152 vhdl_ty ty = Maybe.fromMaybe
153   (error $ "Unsupported Haskell type: " ++ (showSDoc $ ppr ty))
154   (vhdl_ty_maybe ty)
155
156 -- Translate a Haskell type to a VHDL type
157 vhdl_ty_maybe :: Type.Type -> Maybe AST.TypeMark
158 vhdl_ty_maybe ty =
159   case Type.splitTyConApp_maybe ty of
160     Just (tycon, args) ->
161       let name = TyCon.tyConName tycon in
162         -- TODO: Do something more robust than string matching
163         case Name.getOccString name of
164           "Bit"      -> Just bit_ty
165           otherwise  -> Nothing
166     otherwise -> Nothing
167
168 -- Shortcut
169 mkVHDLId :: String -> AST.VHDLId
170 mkVHDLId = AST.unsafeVHDLBasicId