b4301a3f1a0b6c3451c0636025bce2a8a947900d
[matthijs/master-project/cλash.git] / Translator.hs
1 module Translator 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 qualified Control.Monad.State as State
12 import Name
13 import qualified Data.Map as Map
14 import Data.Generics
15 import NameEnv ( lookupNameEnv )
16 import HscTypes ( cm_binds, cm_types )
17 import MonadUtils ( liftIO )
18 import Outputable ( showSDoc, ppr )
19 import GHC.Paths ( libdir )
20 import DynFlags ( defaultDynFlags )
21 import List ( find )
22 import qualified List
23 import qualified Monad
24
25 -- The following modules come from the ForSyDe project. They are really
26 -- internal modules, so ForSyDe.cabal has to be modified prior to installing
27 -- ForSyDe to get access to these modules.
28 import qualified ForSyDe.Backend.VHDL.AST as AST
29 import qualified ForSyDe.Backend.VHDL.Ppr
30 import qualified ForSyDe.Backend.VHDL.FileIO
31 import qualified ForSyDe.Backend.Ppr
32 -- This is needed for rendering the pretty printed VHDL
33 import Text.PrettyPrint.HughesPJ (render)
34
35 import TranslatorTypes
36 import Pretty
37 import Flatten
38 import qualified VHDL
39
40 main = 
41     do
42       defaultErrorHandler defaultDynFlags $ do
43         runGhc (Just libdir) $ do
44           dflags <- getSessionDynFlags
45           setSessionDynFlags dflags
46           --target <- guessTarget "adder.hs" Nothing
47           --liftIO (print (showSDoc (ppr (target))))
48           --liftIO $ printTarget target
49           --setTargets [target]
50           --load LoadAllTargets
51           --core <- GHC.compileToCoreSimplified "Adders.hs"
52           core <- GHC.compileToCoreSimplified "Adders.hs"
53           --liftIO $ printBinds (cm_binds core)
54           let binds = Maybe.mapMaybe (findBind (cm_binds core)) ["sfull_adder"]
55           liftIO $ putStr $ prettyShow binds
56           -- Turn bind into VHDL
57           let (vhdl, sess) = State.runState (mkVHDL binds) (VHDLSession core 0 Map.empty)
58           liftIO $ putStr $ render $ ForSyDe.Backend.Ppr.ppr vhdl
59           liftIO $ ForSyDe.Backend.VHDL.FileIO.writeDesignFile vhdl "../vhdl/vhdl/output.vhdl"
60           liftIO $ putStr $ "\n\nFinal session:\n" ++ prettyShow sess ++ "\n\n"
61           return ()
62   where
63     -- Turns the given bind into VHDL
64     mkVHDL binds = do
65       -- Add the builtin functions
66       mapM addBuiltIn builtin_funcs
67       -- Create entities and architectures for them
68       mapM processBind binds
69       return $ AST.DesignFile 
70         []
71         []
72
73 findBind :: [CoreBind] -> String -> Maybe CoreBind
74 findBind binds lookfor =
75   -- This ignores Recs and compares the name of the bind with lookfor,
76   -- disregarding any namespaces in OccName and extra attributes in Name and
77   -- Var.
78   find (\b -> case b of 
79     Rec l -> False
80     NonRec var _ -> lookfor == (occNameString $ nameOccName $ getName var)
81   ) binds
82
83 -- | Processes the given bind as a top level bind.
84 processBind ::
85   CoreBind                        -- The bind to process
86   -> VHDLState ()
87
88 processBind  (Rec _) = error "Recursive binders not supported"
89 processBind bind@(NonRec var expr) = do
90   -- Create the function signature
91   let ty = CoreUtils.exprType expr
92   let hsfunc = mkHsFunction var ty
93   flattenBind hsfunc bind
94
95 -- | Flattens the given bind into the given signature and adds it to the
96 --   session. Then (recursively) finds any functions it uses and does the same
97 --   with them.
98 flattenBind ::
99   HsFunction                         -- The signature to flatten into
100   -> CoreBind                        -- The bind to flatten
101   -> VHDLState ()
102
103 flattenBind _ (Rec _) = error "Recursive binders not supported"
104
105 flattenBind hsfunc bind@(NonRec var expr) = do
106   -- Flatten the function
107   let flatfunc = flattenFunction hsfunc bind
108   addFunc hsfunc
109   setFlatFunc hsfunc flatfunc
110   let used_hsfuncs = map appFunc (apps flatfunc)
111   State.mapM resolvFunc used_hsfuncs
112   return ()
113
114 -- | Find the given function, flatten it and add it to the session. Then
115 --   (recursively) do the same for any functions used.
116 resolvFunc ::
117   HsFunction        -- | The function to look for
118   -> VHDLState ()
119
120 resolvFunc hsfunc = do
121   -- See if the function is already known
122   func <- getFunc hsfunc
123   case func of
124     -- Already known, do nothing
125     Just _ -> do
126       return ()
127     -- New function, resolve it
128     Nothing -> do
129       -- Get the current module
130       core <- getModule
131       -- Find the named function
132       let bind = findBind (cm_binds core) name
133       case bind of
134         Nothing -> error $ "Couldn't find function " ++ name ++ " in current module."
135         Just b  -> flattenBind hsfunc b
136   where
137     name = hsFuncName hsfunc
138
139 -- | Translate a top level function declaration to a HsFunction. i.e., which
140 --   interface will be provided by this function. This function essentially
141 --   defines the "calling convention" for hardware models.
142 mkHsFunction ::
143   Var.Var         -- ^ The function defined
144   -> Type         -- ^ The function type (including arguments!)
145   -> HsFunction   -- ^ The resulting HsFunction
146
147 mkHsFunction f ty =
148   HsFunction hsname hsargs hsres
149   where
150     hsname  = getOccString f
151     (arg_tys, res_ty) = Type.splitFunTys ty
152     -- The last argument must be state
153     state_ty = last arg_tys
154     state    = useAsState (mkHsValueMap state_ty)
155     -- All but the last argument are inports
156     inports = map (useAsPort . mkHsValueMap)(init arg_tys)
157     hsargs   = inports ++ [state]
158     hsres    = case splitTupleType res_ty of
159       -- Result type must be a two tuple (state, ports)
160       Just [outstate_ty, outport_ty] -> if Type.coreEqType state_ty outstate_ty
161         then
162           Tuple [state, useAsPort (mkHsValueMap outport_ty)]
163         else
164           error $ "Input state type of function " ++ hsname ++ ": " ++ (showSDoc $ ppr state_ty) ++ " does not match output state type: " ++ (showSDoc $ ppr outstate_ty)
165       otherwise                -> error $ "Return type of top-level function " ++ hsname ++ " must be a two-tuple containing a state and output ports."
166
167 -- | Splits a tuple type into a list of element types, or Nothing if the type
168 --   is not a tuple type.
169 splitTupleType ::
170   Type              -- ^ The type to split
171   -> Maybe [Type]   -- ^ The tuples element types
172
173 splitTupleType ty =
174   case Type.splitTyConApp_maybe ty of
175     Just (tycon, args) -> if TyCon.isTupleTyCon tycon 
176       then
177         Just args
178       else
179         Nothing
180     Nothing -> Nothing
181
182 -- | A consise representation of a (set of) ports on a builtin function
183 type PortMap = HsValueMap (String, AST.TypeMark)
184 -- | A consise representation of a builtin function
185 data BuiltIn = BuiltIn String [PortMap] PortMap
186
187 -- | Translate a concise representation of a builtin function to something
188 --   that can be put into FuncMap directly.
189 addBuiltIn :: BuiltIn -> VHDLState ()
190 addBuiltIn (BuiltIn name args res) = do
191     addFunc hsfunc
192   where
193     hsfunc = HsFunction name (map useAsPort args) (useAsPort res)
194
195 builtin_funcs = 
196   [ 
197     BuiltIn "hwxor" [(Single ("a", VHDL.bit_ty)), (Single ("b", VHDL.bit_ty))] (Single ("o", VHDL.bit_ty)),
198     BuiltIn "hwand" [(Single ("a", VHDL.bit_ty)), (Single ("b", VHDL.bit_ty))] (Single ("o", VHDL.bit_ty)),
199     BuiltIn "hwor" [(Single ("a", VHDL.bit_ty)), (Single ("b", VHDL.bit_ty))] (Single ("o", VHDL.bit_ty)),
200     BuiltIn "hwnot" [(Single ("a", VHDL.bit_ty))] (Single ("o", VHDL.bit_ty))
201   ]
202
203 -- vim: set ts=8 sw=2 sts=2 expandtab: