genSignals ::
Type.Type
- -> FlattenState (SignalMap UnnamedSignal)
+ -> FlattenState SignalMap
genSignals ty =
-- First generate a map with the right structure containing the types, and
-- | Marks a signal as the given SigUse, if its id is in the list of id's
-- given.
-markSignals :: SigUse -> [UnnamedSignal] -> (UnnamedSignal, SignalInfo) -> (UnnamedSignal, SignalInfo)
+markSignals :: SigUse -> [SignalId] -> (SignalId, SignalInfo) -> (SignalId, SignalInfo)
markSignals use ids (id, info) =
(id, info')
where
info' = if id `elem` ids then info { sigUse = use} else info
-markSignal :: SigUse -> UnnamedSignal -> (UnnamedSignal, SignalInfo) -> (UnnamedSignal, SignalInfo)
+markSignal :: SigUse -> SignalId -> (SignalId, SignalInfo) -> (SignalId, SignalInfo)
markSignal use id = markSignals use [id]
-- | Flatten a haskell function
flattenExpr ::
BindMap
-> CoreExpr
- -> FlattenState ([SignalMap UnnamedSignal], (SignalMap UnnamedSignal))
+ -> FlattenState ([SignalMap], SignalMap)
flattenExpr binds lam@(Lam b expr) = do
-- Find the type of the binder
-> Var.Var -- The scrutinee
-> CoreBndr -- The binder to bind the scrutinee to
-> CoreAlt -- The single alternative
- -> FlattenState ( [SignalMap UnnamedSignal], SignalMap UnnamedSignal)
+ -> FlattenState ( [SignalMap], SignalMap)
-- See expandExpr
flattenSingleAltCaseExpr binds v b alt@(DataAlt datacon, bind_vars, expr) =
if not (DataCon.isTupleCon datacon)
-- | Filters non-state signals and returns the state number and signal id for
-- state values.
filterState ::
- UnnamedSignal -- | The signal id to look at
+ SignalId -- | The signal id to look at
-> HsValueUse -- | How is this signal used?
- -> Maybe (Int, UnnamedSignal ) -- | The state num and signal id, if this
+ -> Maybe (Int, SignalId ) -- | The state num and signal id, if this
-- signal was used as state
filterState id (State num) =
-- signals in the given maps.
stateList ::
HsUseMap
- -> (SignalMap UnnamedSignal)
- -> [(Int, UnnamedSignal)]
+ -> (SignalMap)
+ -> [(Int, SignalId)]
stateList uses signals =
Maybe.catMaybes $ Foldable.toList $ zipValueMapsWith filterState signals uses
import HsValueMap
-- | A signal identifier
-type UnnamedSignal = Int
+type SignalId = Int
-- | A map of a Haskell value to signal ids
-type SignalMap sigid = HsValueMap sigid
+type SignalMap = HsValueMap SignalId
-- | How is a given (single) value in a function's type (ie, argument or
-- return value) used?
|| Foldable.any isStateUse (hsFuncRes hsfunc)
-- | A flattened function application
-data FApp sigid = FApp {
+data FApp = FApp {
appFunc :: HsFunction,
- appArgs :: [SignalMap sigid],
- appRes :: SignalMap sigid
+ appArgs :: [SignalMap],
+ appRes :: SignalMap
} deriving (Show, Eq)
-- | A conditional signal definition
-data CondDef sigid = CondDef {
- cond :: sigid,
- high :: sigid,
- low :: sigid,
- condRes :: sigid
+data CondDef = CondDef {
+ cond :: SignalId,
+ high :: SignalId,
+ low :: SignalId,
+ condRes :: SignalId
} deriving (Show, Eq)
-- | How is a given signal used in the resulting VHDL?
}
-- | A flattened function
-data FlatFunction' sigid = FlatFunction {
- flat_args :: [SignalMap sigid],
- flat_res :: SignalMap sigid,
- flat_apps :: [FApp sigid],
- flat_conds :: [CondDef sigid],
- flat_sigs :: [(sigid, SignalInfo)]
+data FlatFunction = FlatFunction {
+ flat_args :: [SignalMap],
+ flat_res :: SignalMap,
+ flat_apps :: [FApp],
+ flat_conds :: [CondDef],
+ flat_sigs :: [(SignalId, SignalInfo)]
}
-- | Lookup a given signal id in a signal map, and return the associated
-- SignalInfo. Errors out if the signal was not found.
-signalInfo :: Eq sigid => [(sigid, SignalInfo)] -> sigid -> SignalInfo
+signalInfo :: [(SignalId, SignalInfo)] -> SignalId -> SignalInfo
signalInfo sigs id = Maybe.fromJust $ lookup id sigs
--- | A flat function that does not have its signals named
-type FlatFunction = FlatFunction' UnnamedSignal
-
-- | A list of binds in effect at a particular point of evaluation
type BindMap = [(
CoreBndr, -- ^ The bind name
Either -- ^ The bind value which is either
- (SignalMap UnnamedSignal)
+ (SignalMap)
-- ^ a signal
(
HsValueUse, -- ^ or a HighOrder function
- [UnnamedSignal] -- ^ With these signals already applied to it
+ [SignalId] -- ^ With these signals already applied to it
)
)]
-- | The state during the flattening of a single function
-type FlattenState = State.State ([FApp UnnamedSignal], [CondDef UnnamedSignal], [(UnnamedSignal, SignalInfo)], UnnamedSignal)
+type FlattenState = State.State ([FApp], [CondDef], [(SignalId, SignalInfo)], SignalId)
-- | Add an application to the current FlattenState
-addApp :: (FApp UnnamedSignal) -> FlattenState ()
+addApp :: (FApp) -> FlattenState ()
addApp a = do
(apps, conds, sigs, n) <- State.get
State.put (a:apps, conds, sigs, n)
-- | Add a conditional definition to the current FlattenState
-addCondDef :: (CondDef UnnamedSignal) -> FlattenState ()
+addCondDef :: (CondDef) -> FlattenState ()
addCondDef c = do
(apps, conds, sigs, n) <- State.get
State.put (apps, c:conds, sigs, n)
-- | Generates a new signal id, which is unique within the current flattening.
-genSignalId :: SigUse -> Type.Type -> FlattenState UnnamedSignal
+genSignalId :: SigUse -> Type.Type -> FlattenState SignalId
genSignalId use ty = do
(apps, conds, sigs, n) <- State.get
-- Generate a new numbered but unnamed signal
pPrint (State n) = char 'C' <> int n
pPrint (HighOrder _ _) = text "Higher Order"
-instance Pretty id => Pretty (FlatFunction' id) where
+instance Pretty FlatFunction where
pPrint (FlatFunction args res apps conds sigs) =
(text "Args: ") $$ nest 10 (pPrint args)
$+$ (text "Result: ") $$ nest 10 (pPrint res)
where
ppsig (id, info) = pPrint id <> pPrint info
-instance Pretty id => Pretty (FApp id) where
+instance Pretty FApp where
pPrint (FApp func args res) =
pPrint func <> text " : " <> pPrint args <> text " -> " <> pPrint res
-instance Pretty id => Pretty (CondDef id) where
+instance Pretty CondDef where
pPrint _ = text "TODO"
instance Pretty SignalInfo where
-- | Transforms a flat function application to a VHDL component instantiation.
mkCompInsSm ::
- [(UnnamedSignal, SignalInfo)] -- | The signals in the current architecture
- -> FApp UnnamedSignal -- | The application to look at.
+ [(SignalId, SignalInfo)] -- | The signals in the current architecture
+ -> FApp -- | The application to look at.
-> VHDLState AST.CompInsSm -- | The corresponding VHDL component instantiation.
mkCompInsSm sigs app = do
return $ AST.CompInsSm (mkVHDLId label) (AST.IUEntity (AST.NSimple entity_id)) (AST.PMapAspect portmaps)
mkAssocElems ::
- [(UnnamedSignal, SignalInfo)] -- | The signals in the current architecture
- -> FApp UnnamedSignal -- | The application to look at.
+ [(SignalId, SignalInfo)] -- | The signals in the current architecture
+ -> FApp -- | The application to look at.
-> Entity -- | The entity to map against.
-> [AST.AssocElem] -- | The resulting port maps
sigs = (map (lookupSigName sigmap) (arg_sigs ++ res_sigs))
-- | Look up a signal in the signal name map
-lookupSigName :: [(UnnamedSignal, SignalInfo)] -> UnnamedSignal -> String
+lookupSigName :: [(SignalId, SignalInfo)] -> SignalId -> String
lookupSigName sigs sig = name
where
info = Maybe.fromMaybe
import qualified ForSyDe.Backend.VHDL.AST as AST
import FlattenTypes
+import HsValueMap
-- | A mapping from a haskell structure to the corresponding VHDL port
-- signature, or Nothing for values that do not translate to a port.
-type VHDLSignalMap = SignalMap (Maybe (AST.VHDLId, AST.TypeMark))
+type VHDLSignalMap = HsValueMap (Maybe (AST.VHDLId, AST.TypeMark))
-- A description of a VHDL entity. Contains both the entity itself as well as
-- info on how to map a haskell value (argument / result) on to the entity's