map (Arrow.second $ AST.DesignFile full_context) units
where
- init_session = VHDLSession Map.empty Map.empty Map.empty Map.empty globalNameTable
+ init_session = VHDLState Map.empty Map.empty Map.empty Map.empty globalNameTable
(units, final_session) =
State.runState (createLibraryUnits binds) init_session
tyfun_decls = Map.elems (final_session ^.vsTypeFuns)
createLibraryUnits ::
[(CoreSyn.CoreBndr, CoreSyn.CoreExpr)]
- -> VHDLState [(AST.VHDLId, [AST.LibraryUnit])]
+ -> VHDLSession [(AST.VHDLId, [AST.LibraryUnit])]
createLibraryUnits binds = do
entities <- Monad.mapM createEntity binds
-- | Create an entity for a given function
createEntity ::
(CoreSyn.CoreBndr, CoreSyn.CoreExpr) -- | The function
- -> VHDLState AST.EntityDec -- | The resulting entity
+ -> VHDLSession AST.EntityDec -- | The resulting entity
createEntity (fname, expr) = do
-- Strip off lambda's, these will be arguments
mkMap ::
--[(SignalId, SignalInfo)]
CoreSyn.CoreBndr
- -> VHDLState VHDLSignalMapElement
+ -> VHDLSession VHDLSignalMapElement
-- We only need the vsTypes element from the state
mkMap = (\bndr ->
let
-- | Create an architecture for a given function
createArchitecture ::
(CoreSyn.CoreBndr, CoreSyn.CoreExpr) -- ^ The function
- -> VHDLState AST.ArchBody -- ^ The architecture for this function
+ -> VHDLSession AST.ArchBody -- ^ The architecture for this function
createArchitecture (fname, expr) = do
signaturemap <- getA vsSignatures
(sigName info)
-}
-mkSigDec :: CoreSyn.CoreBndr -> VHDLState (Maybe AST.SigDec)
+mkSigDec :: CoreSyn.CoreBndr -> VHDLSession (Maybe AST.SigDec)
mkSigDec bndr =
if True then do --isInternalSigUse use || isStateSigUse use then do
type_mark <- vhdl_ty $ Var.varType bndr
-- | Transforms a core binding into a VHDL concurrent statement
mkConcSm ::
(CoreSyn.CoreBndr, CoreSyn.CoreExpr) -- ^ The binding to process
- -> VHDLState [AST.ConcSm] -- ^ The corresponding VHDL component instantiations.
+ -> VHDLSession [AST.ConcSm] -- ^ The corresponding VHDL component instantiations.
-- Ignore Cast expressions, they should not longer have any meaning as long as
]
-- Translate a Haskell type to a VHDL type, generating a new type if needed.
-vhdl_ty :: Type.Type -> VHDLState AST.TypeMark
+vhdl_ty :: Type.Type -> VHDLSession AST.TypeMark
vhdl_ty ty = do
typemap <- getA vsTypes
let builtin_ty = do -- See if this is a tycon and lookup its name
Nothing -> error $ "Unsupported Haskell type: " ++ pprString ty
-- Construct a new VHDL type for the given Haskell type.
-construct_vhdl_ty :: Type.Type -> VHDLState (Maybe (AST.TypeMark, Either AST.TypeDef AST.SubtypeIn))
+construct_vhdl_ty :: Type.Type -> VHDLSession (Maybe (AST.TypeMark, Either AST.TypeDef AST.SubtypeIn))
construct_vhdl_ty ty = do
case Type.splitTyConApp_maybe ty of
Just (tycon, args) -> do
Nothing -> return $ Nothing
-- | Create VHDL type for a custom tycon
-mk_tycon_ty :: TyCon.TyCon -> [Type.Type] -> VHDLState (Maybe (AST.TypeMark, Either AST.TypeDef AST.SubtypeIn))
+mk_tycon_ty :: TyCon.TyCon -> [Type.Type] -> VHDLSession (Maybe (AST.TypeMark, Either AST.TypeDef AST.SubtypeIn))
mk_tycon_ty tycon args =
case TyCon.tyConDataCons tycon of
-- Not an algebraic type
mk_vector_ty ::
Int -- ^ The length of the vector
-> Type.Type -- ^ The Haskell element type of the Vector
- -> VHDLState (AST.TypeMark, AST.SubtypeIn) -- The typemark created.
+ -> VHDLSession (AST.TypeMark, AST.SubtypeIn) -- The typemark created.
mk_vector_ty len el_ty = do
elem_types_map <- getA vsElemTypes
mk_natural_ty ::
Int -- ^ The minimum bound (> 0)
-> Int -- ^ The maximum bound (> minimum bound)
- -> VHDLState (AST.TypeMark, AST.SubtypeIn) -- The typemark created.
+ -> VHDLSession (AST.TypeMark, AST.SubtypeIn) -- The typemark created.
mk_natural_ty min_bound max_bound = do
let ty_id = mkVHDLExtId $ "nat_" ++ (show min_bound) ++ "_to_" ++ (show max_bound)
let range = AST.ConstraintRange $ AST.SubTypeRange (AST.PrimLit $ (show min_bound)) (AST.PrimLit $ (show max_bound))
-- Finds the field labels for VHDL type generated for the given Core type,
-- which must result in a record type.
-getFieldLabels :: Type.Type -> VHDLState [AST.VHDLId]
+getFieldLabels :: Type.Type -> VHDLSession [AST.VHDLId]
getFieldLabels ty = do
-- Ensure that the type is generated (but throw away it's VHDLId)
vhdl_ty ty
-- A map of a builtin function to VHDL function builder
type NameTable = Map.Map String (Int, Builder )
-data VHDLSession = VHDLSession {
+data VHDLState = VHDLState {
-- | A map of Core type -> VHDL Type
vsTypes_ :: TypeMap,
-- | A map of Elem types -> VHDL Vector Id
}
-- Derive accessors
-$( Data.Accessor.Template.deriveAccessors ''VHDLSession )
+$( Data.Accessor.Template.deriveAccessors ''VHDLState )
-- | The state containing a VHDL Session
-type VHDLState = State.State VHDLSession
+type VHDLSession = State.State VHDLState
-- | A substate containing just the types
type TypeState = State.State TypeMap