module FlattenTypes where
import Data.Traversable
+import qualified Data.Foldable as Foldable
import qualified Control.Monad.State as State
import CoreSyn
}
deriving (Show, Eq, Ord)
+-- | Is this HsValueUse a state use?
+isStateUse :: HsValueUse -> Bool
+isStateUse (State _) = True
+isStateUse _ = False
+
-- | A map from a Haskell value to the use of each single value
type HsUseMap = HsValueMap HsValueUse
hsFuncRes :: HsUseMap
} deriving (Show, Eq, Ord)
+hasState :: HsFunction -> Bool
+hasState hsfunc =
+ any (Foldable.any isStateUse) (hsFuncArgs hsfunc)
+ || Foldable.any isStateUse (hsFuncRes hsfunc)
+
-- | A flattened function application
data FApp sigid = FApp {
appFunc :: HsFunction,
(sigName info)
ty = sigTy info
--- | Create the VHDL AST for an entity
+ -- | Create the VHDL AST for an entity
createEntityAST ::
HsFunction -- | The signature of the function we're working with
-> [VHDLSignalMap] -- | The entity's arguments
vhdl_id = mkEntityId hsfunc
ports = concatMap (mapToPorts AST.In) args
++ mapToPorts AST.Out res
+ ++ clk_port
mapToPorts :: AST.Mode -> VHDLSignalMap -> [AST.IfaceSigDec]
mapToPorts mode m =
map (mkIfaceSigDec mode) (Foldable.toList m)
+ -- Add a clk port if we have state
+ clk_port = if hasState hsfunc
+ then
+ [AST.IfaceSigDec (mkVHDLId "clk") AST.In VHDL.std_logic_ty]
+ else
+ []
-- | Create a port declaration
mkIfaceSigDec ::
bit_ty :: AST.TypeMark
bit_ty = AST.unsafeVHDLBasicId "Bit"
+-- | The VHDL std_logic
+std_logic_ty :: AST.TypeMark
+std_logic_ty = AST.unsafeVHDLBasicId "std_logic"
+
-- Translate a Haskell type to a VHDL type
vhdl_ty :: Type.Type -> AST.TypeMark
vhdl_ty ty = Maybe.fromMaybe