Look up the port names in the session when generating an architecture.
[matthijs/master-project/cλash.git] / Translator.hs
1 module Main(main) where
2 import GHC
3 import CoreSyn
4 import qualified CoreUtils
5 import qualified Var
6 import qualified Type
7 import qualified TyCon
8 import qualified DataCon
9 import qualified Maybe
10 import qualified Module
11 import Name
12 import Data.Generics
13 import NameEnv ( lookupNameEnv )
14 import HscTypes ( cm_binds, cm_types )
15 import MonadUtils ( liftIO )
16 import Outputable ( showSDoc, ppr )
17 import GHC.Paths ( libdir )
18 import DynFlags ( defaultDynFlags )
19 import List ( find )
20 -- The following modules come from the ForSyDe project. They are really
21 -- internal modules, so ForSyDe.cabal has to be modified prior to installing
22 -- ForSyDe to get access to these modules.
23 import qualified ForSyDe.Backend.VHDL.AST as AST
24 import qualified ForSyDe.Backend.VHDL.Ppr
25 import qualified ForSyDe.Backend.Ppr
26 -- This is needed for rendering the pretty printed VHDL
27 import Text.PrettyPrint.HughesPJ (render)
28
29 main = 
30                 do
31                         defaultErrorHandler defaultDynFlags $ do
32                                 runGhc (Just libdir) $ do
33                                         dflags <- getSessionDynFlags
34                                         setSessionDynFlags dflags
35                                         --target <- guessTarget "adder.hs" Nothing
36                                         --liftIO (print (showSDoc (ppr (target))))
37                                         --liftIO $ printTarget target
38                                         --setTargets [target]
39                                         --load LoadAllTargets
40                                         --core <- GHC.compileToCoreSimplified "Adders.hs"
41                                         core <- GHC.compileToCoreSimplified "Adders.hs"
42                                         liftIO $ printBinds (cm_binds core)
43                                         let bind = findBind "half_adder" (cm_binds core)
44                                         let NonRec var expr = bind
45                                         let sess = VHDLSession 0 builtin_funcs
46                                         let (sess', name, f) = mkHWFunction sess bind
47                                         let sess = addFunc sess' name f
48                                         liftIO $ putStr $ showSDoc $ ppr expr
49                                         liftIO $ putStr "\n\n"
50                                         liftIO $ putStr $ render $ ForSyDe.Backend.Ppr.ppr $ getArchitecture sess bind
51                                         return expr
52
53 printTarget (Target (TargetFile file (Just x)) obj Nothing) =
54         print $ show file
55
56 printBinds [] = putStr "done\n\n"
57 printBinds (b:bs) = do
58         printBind b
59         putStr "\n"
60         printBinds bs
61
62 printBind (NonRec b expr) = do
63         putStr "NonRec: "
64         printBind' (b, expr)
65
66 printBind (Rec binds) = do
67         putStr "Rec: \n"        
68         foldl1 (>>) (map printBind' binds)
69
70 printBind' (b, expr) = do
71         putStr $ getOccString b
72         --putStr $ showSDoc $ ppr expr
73         putStr "\n"
74
75 findBind :: String -> [CoreBind] -> CoreBind
76 findBind lookfor =
77         -- This ignores Recs and compares the name of the bind with lookfor,
78         -- disregarding any namespaces in OccName and extra attributes in Name and
79         -- Var.
80         Maybe.fromJust . find (\b -> case b of 
81                 Rec l -> False
82                 NonRec var _ -> lookfor == (occNameString $ nameOccName $ getName var)
83         )
84
85 -- Accepts a port name and an argument to map to it.
86 -- Returns the appropriate line for in the port map
87 getPortMapEntry binds (Port portname) (Var id) = 
88         (Just (AST.unsafeVHDLBasicId portname)) AST.:=>: (AST.ADName (AST.NSimple (AST.unsafeVHDLBasicId signalname)))
89         where
90                 Port signalname = Maybe.fromMaybe
91                         (error $ "Argument " ++ getOccString id ++ "is unknown")
92                         (lookup id binds)
93
94 getPortMapEntry binds _ a = error $ "Unsupported argument: " ++ (showSDoc $ ppr a)
95
96 getInstantiations ::
97         VHDLSession
98         -> PortNameMap                  -- The arguments that need to be applied to the
99                                                                                                                          -- expression. Should always be the Args
100                                                                                                                          -- constructor.
101         -> PortNameMap               -- The output ports that the expression should generate.
102         -> [(CoreBndr, PortNameMap)] -- A list of bindings in effect
103         -> CoreSyn.CoreExpr          -- The expression to generate an architecture for
104         -> [AST.ConcSm]              -- The resulting VHDL code
105
106 -- A lambda expression binds the first argument (a) to the binder b.
107 getInstantiations sess (Args (a:as)) outs binds (Lam b expr) =
108         getInstantiations sess (Args as) outs ((b, a):binds) expr
109
110 -- A case expression that checks a single variable and has a single
111 -- alternative, can be used to take tuples apart
112 getInstantiations sess args outs binds (Case (Var v) b _ [res]) =
113         case altcon of
114                 DataAlt datacon ->
115                         if (DataCon.isTupleCon datacon) then
116                                 getInstantiations sess args outs binds' expr
117                         else
118                                 error "Data constructors other than tuples not supported"
119                 otherwise ->
120                         error "Case binders other than tuples not supported"
121         where
122                 binds' = (zip bind_vars tuple_ports) ++ binds
123                 (altcon, bind_vars, expr) = res
124                 -- Find the portnamemaps for each of the tuple's elements
125                 Tuple tuple_ports = Maybe.fromMaybe 
126                         (error $ "Case expression uses unknown scrutinee " ++ getOccString v)
127                         (lookup v binds)
128
129 -- An application is an instantiation of a component
130 getInstantiations sess args outs binds app@(App expr arg) =
131         if isTupleConstructor f then
132                 let
133                         Tuple outports = outs
134                         (tys, vals) = splitTupleConstructorArgs fargs
135                 in
136                         concat $ zipWith 
137                                 (\outs' expr' -> getInstantiations sess args outs' binds expr')
138                                 outports vals
139         else
140                 [AST.CSISm comp]
141         where
142                 ((Var f), fargs) = collectArgs app
143                 comp = AST.CompInsSm
144                         (AST.unsafeVHDLBasicId "app")
145                         (AST.IUEntity (AST.NSimple (AST.unsafeVHDLBasicId compname)))
146                         (AST.PMapAspect ports)
147                 compname = getOccString f
148                 hwfunc = Maybe.fromMaybe
149                         (error $ "Function " ++ compname ++ "is unknown")
150                         (lookup compname (funcs sess))
151                 HWFunction (Args inports) outport = hwfunc
152                 ports = 
153                         zipWith (getPortMapEntry binds) inports fargs
154                   ++ mapOutputPorts outport outs
155
156 getInstantiations sess args outs binds expr = 
157         error $ "Unsupported expression" ++ (showSDoc $ ppr $ expr)
158
159 -- Is the given name a (binary) tuple constructor
160 isTupleConstructor :: Var.Var -> Bool
161 isTupleConstructor var =
162         Name.isWiredInName name
163         && Name.nameModule name == tuple_mod
164         && (Name.occNameString $ Name.nameOccName name) == "(,)"
165         where
166                 name = Var.varName var
167                 mod = nameModule name
168                 tuple_mod = Module.mkModule (Module.stringToPackageId "ghc-prim") (Module.mkModuleName "GHC.Tuple")
169
170 -- Split arguments into type arguments and value arguments This is probably
171 -- not really sufficient (not sure if Types can actually occur as value
172 -- arguments...)
173 splitTupleConstructorArgs :: [CoreExpr] -> ([CoreExpr], [CoreExpr])
174 splitTupleConstructorArgs (e:es) =
175         case e of
176                 Type t     -> (e:tys, vals)
177                 otherwise  -> (tys, e:vals)
178         where
179                 (tys, vals) = splitTupleConstructorArgs es
180
181 mapOutputPorts ::
182         PortNameMap         -- The output portnames of the component
183         -> PortNameMap      -- The output portnames and/or signals to map these to
184         -> [AST.AssocElem]  -- The resulting output ports
185
186 -- Map the output port of a component to the output port of the containing
187 -- entity.
188 mapOutputPorts (Port portname) (Port signalname) =
189         [(Just (AST.unsafeVHDLBasicId portname)) AST.:=>: (AST.ADName (AST.NSimple (AST.unsafeVHDLBasicId signalname)))]
190
191 -- Map matching output ports in the tuple
192 mapOutputPorts (Tuple ports) (Tuple signals) =
193         concat (zipWith mapOutputPorts ports signals)
194
195 getArchitecture ::
196         VHDLSession
197         -> CoreBind               -- The binder to expand into an architecture
198         -> AST.ArchBody           -- The resulting architecture
199          
200 getArchitecture sess (Rec _) = error "Recursive binders not supported"
201
202 getArchitecture sess (NonRec var expr) =
203         AST.ArchBody
204                 (AST.unsafeVHDLBasicId "structural")
205                 -- Use unsafe for now, to prevent pulling in ForSyDe error handling
206                 (AST.NSimple (AST.unsafeVHDLBasicId name))
207                 []
208                 (getInstantiations sess (Args inports) outport [] expr)
209         where
210                 name = (getOccString var)
211                 hwfunc = Maybe.fromMaybe
212                         (error $ "Function " ++ name ++ "is unknown? This should not happen!")
213                         (lookup name (funcs sess))
214                 HWFunction (Args inports) outport = hwfunc
215
216 data PortNameMap =
217         Args [PortNameMap] -- Each of the submaps represent an argument to the
218                            -- function. Should only occur at top level.
219         | Tuple [PortNameMap]
220         | Port  String
221
222 -- Generate a port name map (or multiple for tuple types) in the given direction for
223 -- each type given.
224 getPortNameMapForTys :: String -> Int -> [Type] -> [PortNameMap]
225 getPortNameMapForTys prefix num [] = [] 
226 getPortNameMapForTys prefix num (t:ts) =
227         (getPortNameMapForTy (prefix ++ show num) t) : getPortNameMapForTys prefix (num + 1) ts
228
229 getPortNameMapForTy     :: String -> Type -> PortNameMap
230 getPortNameMapForTy name ty =
231         if (TyCon.isTupleTyCon tycon) then
232                 -- Expand tuples we find
233                 Tuple (getPortNameMapForTys name 0 args)
234         else -- Assume it's a type constructor application, ie simple data type
235                 -- TODO: Add type?
236                 Port name
237         where
238                 (tycon, args) = Type.splitTyConApp ty 
239
240 data HWFunction = HWFunction { -- A function that is available in hardware
241         inPorts   :: PortNameMap,
242         outPorts  :: PortNameMap
243         --entity    :: AST.EntityDec
244 }
245
246 -- Turns a CoreExpr describing a function into a description of its input and
247 -- output ports.
248 mkHWFunction ::
249         VHDLSession
250         -> CoreBind                                -- The core binder to generate the interface for
251         -> (VHDLSession, String, HWFunction)       -- The name of the function and its interface
252
253 mkHWFunction sess (NonRec var expr) =
254         (sess, name, HWFunction (Args inports) outport)
255         where
256                 name = (getOccString var)
257                 ty = CoreUtils.exprType expr
258                 (fargs, res) = Type.splitFunTys ty
259                 args = if length fargs == 1 then fargs else (init fargs)
260                 --state = if length fargs == 1 then () else (last fargs)
261                 inports = case args of
262                         -- Handle a single port specially, to prevent an extra 0 in the name
263                         [port] -> [getPortNameMapForTy "portin" port]
264                         ps     -> getPortNameMapForTys "portin" 0 ps
265                 outport = getPortNameMapForTy "portout" res
266
267 mkHWFunction sess (Rec _) =
268         error "Recursive binders not supported"
269
270 data VHDLSession = VHDLSession {
271         nameCount :: Int,                      -- A counter that can be used to generate unique names
272         funcs     :: [(String, HWFunction)]    -- All functions available, indexed by name
273 }
274
275 -- Add the function to the session
276 addFunc :: VHDLSession -> String -> HWFunction -> VHDLSession
277 addFunc sess name f =
278         sess {funcs = (name, f) : (funcs sess) }
279
280 builtin_funcs = 
281         [ 
282                 ("hwxor", HWFunction (Args [Port "a", Port "b"]) (Port "o")),
283                 ("hwand", HWFunction (Args [Port "a", Port "b"]) (Port "o"))
284         ]