Add facilities for builtin functions.
[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 flattenBind 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 -- | Flattens the given bind and adds it to the session. Then (recursively)
84 --   finds any functions it uses and does the same with them.
85 flattenBind ::
86   CoreBind                        -- The binder to flatten
87   -> VHDLState ()
88
89 flattenBind (Rec _) = error "Recursive binders not supported"
90
91 flattenBind bind@(NonRec var expr) = do
92   -- Create the function signature
93   let ty = CoreUtils.exprType expr
94   let hsfunc = mkHsFunction var ty
95   --hwfunc <- mkHWFunction bind hsfunc
96   -- Add it to the session
97   --addFunc hsfunc hwfunc 
98   let flatfunc = flattenFunction hsfunc bind
99   addFunc hsfunc
100   setFlatFunc hsfunc flatfunc
101   let used_hsfuncs = map appFunc (apps flatfunc)
102   State.mapM resolvFunc used_hsfuncs
103   return ()
104
105 -- | Find the given function, flatten it and add it to the session. Then
106 --   (recursively) do the same for any functions used.
107 resolvFunc ::
108   HsFunction        -- | The function to look for
109   -> VHDLState ()
110
111 resolvFunc hsfunc = do
112   -- See if the function is already known
113   func <- getFunc hsfunc
114   case func of
115     -- Already known, do nothing
116     Just _ -> do
117       return ()
118     -- New function, resolve it
119     Nothing -> do
120       -- Get the current module
121       core <- getModule
122       -- Find the named function
123       let bind = findBind (cm_binds core) name
124       case bind of
125         Nothing -> error $ "Couldn't find function " ++ name ++ " in current module."
126         Just b  -> flattenBind b
127   where
128     name = hsFuncName hsfunc
129
130 -- | Translate a top level function declaration to a HsFunction. i.e., which
131 --   interface will be provided by this function. This function essentially
132 --   defines the "calling convention" for hardware models.
133 mkHsFunction ::
134   Var.Var         -- ^ The function defined
135   -> Type         -- ^ The function type (including arguments!)
136   -> HsFunction   -- ^ The resulting HsFunction
137
138 mkHsFunction f ty =
139   HsFunction hsname hsargs hsres
140   where
141     hsname  = getOccString f
142     (arg_tys, res_ty) = Type.splitFunTys ty
143     -- The last argument must be state
144     state_ty = last arg_tys
145     state    = useAsState (mkHsValueMap state_ty)
146     -- All but the last argument are inports
147     inports = map (useAsPort . mkHsValueMap)(init arg_tys)
148     hsargs   = inports ++ [state]
149     hsres    = case splitTupleType res_ty of
150       -- Result type must be a two tuple (state, ports)
151       Just [outstate_ty, outport_ty] -> if Type.coreEqType state_ty outstate_ty
152         then
153           Tuple [state, useAsPort (mkHsValueMap outport_ty)]
154         else
155           error $ "Input state type of function " ++ hsname ++ ": " ++ (showSDoc $ ppr state_ty) ++ " does not match output state type: " ++ (showSDoc $ ppr outstate_ty)
156       otherwise                -> error $ "Return type of top-level function " ++ hsname ++ " must be a two-tuple containing a state and output ports."
157
158 -- | Splits a tuple type into a list of element types, or Nothing if the type
159 --   is not a tuple type.
160 splitTupleType ::
161   Type              -- ^ The type to split
162   -> Maybe [Type]   -- ^ The tuples element types
163
164 splitTupleType ty =
165   case Type.splitTyConApp_maybe ty of
166     Just (tycon, args) -> if TyCon.isTupleTyCon tycon 
167       then
168         Just args
169       else
170         Nothing
171     Nothing -> Nothing
172
173 -- | A consise representation of a (set of) ports on a builtin function
174 type PortMap = HsValueMap (String, AST.TypeMark)
175 -- | A consise representation of a builtin function
176 data BuiltIn = BuiltIn String [PortMap] PortMap
177
178 -- | Translate a concise representation of a builtin function to something
179 --   that can be put into FuncMap directly.
180 addBuiltIn :: BuiltIn -> VHDLState ()
181 addBuiltIn (BuiltIn name args res) = do
182     addFunc hsfunc
183   where
184     hsfunc = HsFunction name (map useAsPort args) (useAsPort res)
185
186 builtin_funcs = 
187   [ 
188     BuiltIn "hwxor" [(Single ("a", VHDL.bit_ty)), (Single ("b", VHDL.bit_ty))] (Single ("o", VHDL.bit_ty))
189   ]
190
191 -- vim: set ts=8 sw=2 sts=2 expandtab: