Make a proper HsFunction for top-level functions.
[matthijs/master-project/cλash.git] / Translator.hs
index 8f1c3fd4d6e1a49326c2086cca2b756b8fc798ac..37ba81dccceced799119d95b046f48391c787feb 100644 (file)
@@ -57,16 +57,11 @@ main =
     mkVHDL binds = do
       -- Add the builtin functions
       mapM (uncurry addFunc) builtin_funcs
-      -- Get the function signatures
-      funcs <- mapM mkHWFunction binds
-      -- Add them to the session
-      mapM (uncurry addFunc) funcs
-      let entities = map getEntity (snd $ unzip funcs)
-      -- Create architectures for them
-      archs <- mapM getArchitecture binds
+      -- Create entities and architectures for them
+      units <- mapM expandBind binds
       return $ AST.DesignFile 
         []
-        ((map AST.LUEntity entities) ++ (map AST.LUArch archs))
+        (concat units)
 
 printTarget (Target (TargetFile file (Just x)) obj Nothing) =
   print $ show file
@@ -254,7 +249,7 @@ expandApplicationExpr binds ty f args = do
   -- Generate a unique name for the application
   appname <- uniqueName ("app_" ++ name)
   -- Lookup the hwfunction to instantiate
-  HWFunction vhdl_id inports outport <- getHWFunc name
+  HWFunction vhdl_id inports outport <- getHWFunc (appToHsFunction f args ty)
   -- Expand each of the args, so each of them is reduced to output signals
   (arg_signal_decls, arg_statements, arg_res_signals) <- expandArgs binds args
   -- Bind each of the input ports to the expanded arguments
@@ -357,16 +352,34 @@ mapOutputPorts (Single (portname, _)) (Single (signalname, _)) =
 mapOutputPorts (Tuple ports) (Tuple signals) =
   concat (zipWith mapOutputPorts ports signals)
 
+expandBind ::
+  CoreBind                        -- The binder to expand into VHDL
+  -> VHDLState [AST.LibraryUnit]  -- The resulting VHDL
+
+expandBind (Rec _) = error "Recursive binders not supported"
+
+expandBind bind@(NonRec var expr) = do
+  -- Create the function signature
+  hwfunc <- mkHWFunction bind
+  let ty = CoreUtils.exprType expr
+  let hsfunc = mkHsFunction var ty
+  -- Add it to the session
+  addFunc hsfunc hwfunc 
+  arch <- getArchitecture hwfunc expr
+  let entity = getEntity hwfunc
+  return $ [
+    AST.LUEntity entity,
+    AST.LUArch arch ]
+
 getArchitecture ::
-  CoreBind                  -- The binder to expand into an architecture
+  HWFunction                -- The function to generate an architecture for
+  -> CoreExpr               -- The expression that is bound to the function
   -> VHDLState AST.ArchBody -- The resulting architecture
    
-getArchitecture (Rec _) = error "Recursive binders not supported"
-
-getArchitecture (NonRec var expr) = do
-  let name = (getOccString var)
-  HWFunction vhdl_id inports outport <- getHWFunc name
-  sess <- State.get
+getArchitecture hwfunc expr = do
+  -- Unpack our hwfunc
+  let HWFunction vhdl_id inports outport = hwfunc
+  -- Expand the expression into an architecture body
   (signal_decls, statements, arg_signals, res_signal) <- expandExpr [] expr
   let inport_assigns = concat $ zipWith createSignalAssignments arg_signals inports
   let outport_assigns = createSignalAssignments outport res_signal
@@ -428,7 +441,30 @@ type SignalNameMap = HsValueMap (AST.VHDLId, AST.TypeMark)
 data HsValueMap mapto =
   Tuple [HsValueMap mapto]
   | Single mapto
-  deriving (Show)
+  deriving (Show, Eq)
+
+-- | Creates a HsValueMap with the same structure as the given type, using the
+--   given function for mapping the single types.
+mkHsValueMap ::
+  (Type -> HsValueMap mapto)    -- ^ A function to map single value Types
+                                --   (basically anything but tuples) to a
+                                --   HsValueMap (not limited to the Single
+                                --   constructor)
+  -> Type                       -- ^ The type to map to a HsValueMap
+  -> HsValueMap mapto           -- ^ The resulting map
+
+mkHsValueMap f ty =
+  case Type.splitTyConApp_maybe ty of
+    Just (tycon, args) ->
+      if (TyCon.isTupleTyCon tycon) 
+        then
+          -- Handle tuple construction especially
+          Tuple (map (mkHsValueMap f) args)
+        else
+          -- And let f handle the rest
+          f ty
+    -- And let f handle the rest
+    Nothing -> f ty
 
 -- Generate a port name map (or multiple for tuple types) in the given direction for
 -- each type given.
@@ -458,10 +494,10 @@ data HWFunction = HWFunction { -- A function that is available in hardware
 -- output ports.
 mkHWFunction ::
   CoreBind                                   -- The core binder to generate the interface for
-  -> VHDLState (String, HWFunction)          -- The name of the function and its interface
+  -> VHDLState HWFunction                    -- The function interface
 
 mkHWFunction (NonRec var expr) =
-    return (name, HWFunction (mkVHDLId name) inports outport)
+    return $ HWFunction (mkVHDLId name) inports outport
   where
     name = getOccString var
     ty = CoreUtils.exprType expr
@@ -477,27 +513,74 @@ mkHWFunction (NonRec var expr) =
 mkHWFunction (Rec _) =
   error "Recursive binders not supported"
 
+-- | How is a given (single) value in a function's type (ie, argument or
+-- return value) used?
+data HsValueUse = 
+  Port -- ^ Use it as a port (input or output)
+  deriving (Show, Eq)
+
+-- | This type describes a particular use of a Haskell function and is used to
+--   look up an appropriate hardware description.  
+data HsFunction = HsFunction {
+  hsName :: String,                      -- ^ What was the name of the original Haskell function?
+  hsArgs :: [HsValueMap HsValueUse],     -- ^ How are the arguments used?
+  hsRes  :: HsValueMap HsValueUse        -- ^ How is the result value used?
+} deriving (Show, Eq)
+
+-- | Translate a function application to a HsFunction. i.e., which function
+--   do you need to translate this function application.
+appToHsFunction ::
+  Var.Var         -- ^ The function to call
+  -> [CoreExpr]   -- ^ The function arguments
+  -> Type         -- ^ The return type
+  -> HsFunction   -- ^ The needed HsFunction
+
+appToHsFunction f args ty =
+  HsFunction hsname hsargs hsres
+  where
+    mkPort = \x -> Single Port
+    hsargs = map (mkHsValueMap mkPort . CoreUtils.exprType) args
+    hsres  = mkHsValueMap mkPort ty
+    hsname = getOccString f
+
+-- | Translate a top level function declaration to a HsFunction. i.e., which
+--   interface will be provided by this function. This function essentially
+--   defines the "calling convention" for hardware models.
+mkHsFunction ::
+  Var.Var         -- ^ The function defined
+  -> Type         -- ^ The function type (including arguments!)
+  -> HsFunction   -- ^ The resulting HsFunction
+
+mkHsFunction f ty =
+  HsFunction hsname hsargs hsres
+  where
+    (arg_tys, res_ty) = Type.splitFunTys ty
+    mkPort = \x -> Single Port
+    hsargs = map (mkHsValueMap mkPort) arg_tys
+    hsres  = mkHsValueMap mkPort res_ty
+    hsname = getOccString f
+
 data VHDLSession = VHDLSession {
-  nameCount :: Int,                      -- A counter that can be used to generate unique names
-  funcs     :: [(String, HWFunction)]    -- All functions available, indexed by name
+  nameCount :: Int,                       -- A counter that can be used to generate unique names
+  funcs     :: [(HsFunction, HWFunction)] -- All functions available
 } deriving (Show)
 
 type VHDLState = State.State VHDLSession
 
 -- Add the function to the session
-addFunc :: String -> HWFunction -> VHDLState ()
-addFunc name f = do
+addFunc :: HsFunction -> HWFunction -> VHDLState ()
+addFunc hsfunc hwfunc = do
   fs <- State.gets funcs -- Get the funcs element from the session
-  State.modify (\x -> x {funcs = (name, f) : fs }) -- Prepend name and f
+  State.modify (\x -> x {funcs = (hsfunc, hwfunc) : fs }) -- Prepend name and f
 
 -- Lookup the function with the given name in the current session. Errors if
 -- it was not found.
-getHWFunc :: String -> VHDLState HWFunction
-getHWFunc name = do
+getHWFunc :: HsFunction -> VHDLState HWFunction
+getHWFunc hsfunc = do
   fs <- State.gets funcs -- Get the funcs element from the session
   return $ Maybe.fromMaybe
-    (error $ "Function " ++ name ++ "is unknown? This should not happen!")
-    (lookup name fs)
+    (error $ "Function " ++ (hsName hsfunc) ++ "is unknown? This should not happen!")
+    (lookup hsfunc fs)
 
 -- Makes the given name unique by appending a unique number.
 -- This does not do any checking against existing names, so it only guarantees
@@ -514,10 +597,10 @@ mkVHDLId = AST.unsafeVHDLBasicId
 
 builtin_funcs = 
   [ 
-    ("hwxor", HWFunction (mkVHDLId "hwxor") [Single (mkVHDLId "a", vhdl_bit_ty), Single (mkVHDLId "b", vhdl_bit_ty)] (Single (mkVHDLId "o", vhdl_bit_ty))),
-    ("hwand", HWFunction (mkVHDLId "hwand") [Single (mkVHDLId "a", vhdl_bit_ty), Single (mkVHDLId "b", vhdl_bit_ty)] (Single (mkVHDLId "o", vhdl_bit_ty))),
-    ("hwor", HWFunction (mkVHDLId "hwor") [Single (mkVHDLId "a", vhdl_bit_ty), Single (mkVHDLId "b", vhdl_bit_ty)] (Single (mkVHDLId "o", vhdl_bit_ty))),
-    ("hwnot", HWFunction (mkVHDLId "hwnot") [Single (mkVHDLId "i", vhdl_bit_ty)] (Single (mkVHDLId "o", vhdl_bit_ty)))
+    (HsFunction "hwxor" [(Single Port), (Single Port)] (Single Port), HWFunction (mkVHDLId "hwxor") [Single (mkVHDLId "a", vhdl_bit_ty), Single (mkVHDLId "b", vhdl_bit_ty)] (Single (mkVHDLId "o", vhdl_bit_ty))),
+    (HsFunction "hwand" [(Single Port), (Single Port)] (Single Port), HWFunction (mkVHDLId "hwand") [Single (mkVHDLId "a", vhdl_bit_ty), Single (mkVHDLId "b", vhdl_bit_ty)] (Single (mkVHDLId "o", vhdl_bit_ty))),
+    (HsFunction "hwor" [(Single Port), (Single Port)] (Single Port), HWFunction (mkVHDLId "hwor") [Single (mkVHDLId "a", vhdl_bit_ty), Single (mkVHDLId "b", vhdl_bit_ty)] (Single (mkVHDLId "o", vhdl_bit_ty))),
+    (HsFunction "hwnot" [(Single Port)] (Single Port), HWFunction (mkVHDLId "hwnot") [Single (mkVHDLId "i", vhdl_bit_ty)] (Single (mkVHDLId "o", vhdl_bit_ty)))
   ]
 
 vhdl_bit_ty :: AST.TypeMark