module ForSyDe.Deep.Backend.VHDL.Traverse
(writeVHDLM,
module ForSyDe.Deep.Backend.VHDL.Traverse.VHDLM) where
import ForSyDe.Deep.Backend.VHDL.Traverse.VHDLM
import ForSyDe.Deep.Backend.VHDL.Translate
import ForSyDe.Deep.Backend.VHDL.Generate
import ForSyDe.Deep.Backend.VHDL.FileIO
import ForSyDe.Deep.Backend.VHDL.AST
import ForSyDe.Deep.Backend.VHDL.Quartus (callQuartus)
import ForSyDe.Deep.Backend.VHDL.Modelsim
import ForSyDe.Deep.ForSyDeErr
import ForSyDe.Deep.System.SysDef
import ForSyDe.Deep.Process.ProcVal
import ForSyDe.Deep.Process.ProcFun
import ForSyDe.Deep.Netlist.Traverse
import ForSyDe.Deep.Netlist
import ForSyDe.Deep.OSharing
import Control.Monad.State
import System.Directory
import System.FilePath
import Data.Maybe (fromJust, isJust)
writeVHDLM :: VHDLM ()
writeVHDLM = do
rootDir <- gets (sid.globalSysDef.global)
let workDir = rootDir </> "vhdl" </> "work"
liftIO $ createDirectoryIfMissing True workDir
liftIO $ setCurrentDirectory workDir
rec <- isRecursiveSet
when rec $ do subs <- gets (subSys.globalSysDef.global)
let writeSub s =
withLocalST (initLocalST ((readURef.unPrimSysDef) s))
writeLocalVHDLM
mapM_ writeSub subs
writeLocalVHDLM
let libDir = ".." </> rootDir ++ "_lib"
liftIO $ createDirectoryIfMissing True libDir
liftIO $ setCurrentDirectory $ libDir
writeGlobalVHDLM
liftIO $ setCurrentDirectory ".."
callQuartus
compile <- isCompileModelsimSet
when compile compileResultsModelsim
liftIO $ setCurrentDirectory (".." </> "..")
writeGlobalVHDLM :: VHDLM ()
writeGlobalVHDLM = do
gSysId <- gets (sid.globalSysDef.global)
debugMsg $ "Generating global system library for `" ++ gSysId ++ "' ...\n"
globalRes <- gets (globalRes.global)
let libName = gSysId ++ "_lib"
libDesignFile = genLibDesignFile globalRes
liftIO $ writeDesignFile libDesignFile (libName ++ ".vhd")
writeLocalVHDLM :: VHDLM ()
writeLocalVHDLM = do
gSysDefVal <- gets (globalSysDef.global)
lSysDefVal <- gets (currSysDef.local)
let lSysDefId = sid lSysDefVal
debugMsg $ "Compiling system definition `" ++ lSysDefId ++ "' ...\n"
let nl = netlist lSysDefVal
intOutsInfo <- traverseVHDLM nl
LocalTravResult decs stms <- gets (localRes.local)
let finalLogic = logic lSysDefVal
entity@(EntityDec _ eIface) <- transSysDef2Ent finalLogic lSysDefVal
let outIds = mapFilter (\(IfaceSigDec id _ _) -> id)
(\(IfaceSigDec _ m _) -> m == Out) eIface
outAssigns = genOutAssigns outIds intOutsInfo
finalRes = LocalTravResult decs (stms ++ outAssigns)
sysDesignFile = genSysDesignFile (sid gSysDefVal) entity finalRes
liftIO $ writeDesignFile sysDesignFile (lSysDefId ++ ".vhd")
where mapFilter f p = foldr (\x ys -> if p x then (f x):ys else ys) []
traverseVHDLM :: Netlist [] -> VHDLM [IntSignalInfo]
traverseVHDLM = traverseSEIO newVHDL defineVHDL
newVHDL :: NlNode NlSignal -> VHDLM [(NlNodeOut, IntSignalInfo)]
newVHDL node = case node of
InPort id -> do vId <- transPortId2VHDL id
return [(InPortOut, vId)]
Proc pid proc -> withProcC pid $ do
vpid <- transProcId2VHDL pid
let procSuffSignal sigSuffix = unsafeIdAppend vpid sigSuffix
multOutTags =
zipWith (\tag n -> (tag, procSuffSignal $ outSuffix ++ show n))
(outTags node) [(1::Int)..]
case proc of
Const _ -> return [(ConstOut, procSuffSignal outSuffix)]
ZipWithNSY _ _ -> return [(ZipWithNSYOut, procSuffSignal outSuffix)]
ZipWithxSY _ _ -> return [(ZipWithxSYOut, procSuffSignal outSuffix)]
UnzipNSY _ _ _ -> return multOutTags
UnzipxSY _ _ _ _ -> return multOutTags
DelaySY _ _ -> return [(DelaySYOut, procSuffSignal outSuffix)]
SysIns _ _ ->
return multOutTags
where outSuffix = "_out"
defineVHDL :: [(NlNodeOut, IntSignalInfo)]
-> NlNode IntSignalInfo
-> VHDLM ()
defineVHDL outs ins = do
case (outs,ins) of
(_, InPort _) -> return ()
(outs, Proc pid proc) -> withProcC pid $ do
let vPid = unsafeVHDLExtId pid
case (outs, proc) of
([(ConstOut, intSig)], Const ProcVal{valAST=ast}) -> do
let cons = expVal ast
dec <- withProcValC cons $ transVHDLName2SigDec
intSig (expTyp ast) (Just cons)
addSigDec dec
([(ZipWithNSYOut, intOut)], ZipWithNSY f intIns) -> do
(block, dec) <- transZipWithN2Block vPid intIns (tpfloc f) (tast f) intOut
addStm $ CSBSm block
addSigDec dec
([(ZipWithxSYOut, intOut)], ZipWithxSY f intIns) -> do
(block, dec) <- transZipWithx2Block vPid intIns (tpfloc f) (tast f) intOut
addStm $ CSBSm block
addSigDec dec
(intOuts, UnzipNSY outTypes _ intIn) -> do
(block, decs) <- transUnzipNSY2Block vPid intIn (map snd intOuts) outTypes
addStm $ CSBSm block
mapM_ addSigDec decs
(intOuts, UnzipxSY typ size _ intIn) -> do
(block, decs) <- transUnzipxSY2Block vPid intIn (map snd intOuts) typ size
addStm $ CSBSm block
mapM_ addSigDec decs
([(DelaySYOut, intOut)], DelaySY initExp intIn) -> do
(block, dec) <- transDelay2Block vPid intIn (valAST initExp) intOut
addStm $ CSBSm block
addSigDec dec
(intOuts, SysIns pSys intIns) -> do
let parentSysRef = unPrimSysDef pSys
parentSysVal = readURef parentSysRef
parentLogic = logic parentSysVal
parentInIface = iIface parentSysVal
parentOutIface = oIface parentSysVal
typedOuts = zipWith (\(_, t) (_, int) -> (int,t)) parentOutIface
intOuts
parentId = sid parentSysVal
(mCompIns, decs) <- transSysIns2CompIns parentLogic
vPid
intIns
typedOuts
parentId
(map fst parentInIface)
(map fst parentOutIface)
when (isJust mCompIns) (addStm $ CSISm $ fromJust mCompIns)
mapM_ addSigDec decs
_ -> intError "ForSyDe.Backend.VHDL.Traverse.defineVHDL" InconsOutTag