module ForSyDe.Deep.Backend.VHDL.Modelsim (compileResultsModelsim,
executeTestBenchModelsim) where
import ForSyDe.Deep.Backend.VHDL.Traverse.VHDLM
import ForSyDe.Deep.Backend.VHDL.TestBench
import ForSyDe.Deep.System.SysDef
import ForSyDe.Deep.OSharing
import ForSyDe.Deep.ForSyDeErr
import ForSyDe.Deep.Config (getDataDir)
import Data.List (intersperse)
import System.Directory (setCurrentDirectory)
import Control.Monad (liftM, when)
import Control.Monad.State (gets)
import System.Directory (findExecutable, getTemporaryDirectory)
import System.Process (runProcess, waitForProcess)
import System.Exit (ExitCode(..))
import System.IO
import System.FilePath ((</>))
import qualified Language.Haskell.TH as TH (Exp)
executeTestBenchModelsim :: Maybe Int
-> [[TH.Exp]]
-> VHDLM [[String]]
executeTestBenchModelsim mCycles stimuli= do
cycles <- writeVHDLTestBench mCycles stimuli
sysid <- gets (sid.globalSysDef.global)
liftIO $ setCurrentDirectory (sysid </> "vhdl")
run_vcom ["-93", "-quiet", "-nologo", "-work", "work",
"test" </> (sysid ++ "_tb.vhd")]
tmpdir <- liftIO getTemporaryDirectory
(file, handle) <- liftIO $ openTempFile tmpdir "tb_out.txt"
liftIO $ hClose handle
run_vsim ["-c", "-std_output", file, "-quiet",
"-do", "run " ++ show (cycles*10) ++ " ns; exit",
"work." ++ sysid ++ "_tb"]
handle2 <- liftIO $ openFile file ReadMode
flatOut <- liftIO $ hGetContents handle2
liftIO $ setCurrentDirectory (".." </> "..")
parseTestBenchOut flatOut
compileResultsModelsim :: VHDLM ()
compileResultsModelsim = do
installed <- liftIO $ isModelsimInstalled
when (not installed) (throwFError ModelsimFailed)
sys <- gets (globalSysDef.global)
let sysId = sid sys
syslib = sysId ++ "_lib"
libFile = syslib </> (syslib ++ ".vhd")
workFiles = ("work" </> (sysId ++ ".vhd")) :
map (("work"</>).(++".vhd").sid.readURef.unPrimSysDef)
(subSys sys)
dataPath <- liftIO $ getDataDir
let modelsimForSyDe = dataPath </> "lib" </> "modelsim"
run_vmap ["forsyde", modelsimForSyDe]
let modelsimLib = syslib </> "modelsim"
run_vlib [modelsimLib]
run_vcom ["-93", "-quiet", "-nologo", "-work", modelsimLib, libFile]
run_vmap [syslib, modelsimLib]
let modelsimWork = "work" </> "modelsim"
run_vlib [modelsimWork]
run_vcom ("-93" : "-quiet" : "-nologo" : "-work" : modelsimWork :
"-just" : "e" : workFiles)
run_vcom ("-93" : "-quiet" : "-nologo" : "-work" : modelsimWork :
"-just" : "a" : workFiles)
run_vmap ["work", modelsimWork]
run_vlib :: [String]
-> VHDLM ()
run_vlib = runModelsimCommand "vlib"
run_vmap :: [String]
-> VHDLM ()
run_vmap = runModelsimCommand "vmap"
run_vcom :: [String]
-> VHDLM ()
run_vcom = runModelsimCommand "vcom"
run_vsim :: [String]
-> VHDLM ()
run_vsim = runModelsimCommand "vsim"
runModelsimCommand :: String
-> [String]
-> VHDLM ()
runModelsimCommand command args = do
success <- liftIO $ runWait msg command args
when (not success) (throwFError ModelsimFailed)
where msg = "Running: " ++ command ++ " " ++ (concat $ intersperse " " args)
runWait :: String
-> FilePath
-> [String]
-> IO Bool
runWait msg proc args = do
putStrLn msg
h <- runProcess proc args Nothing Nothing Nothing Nothing Nothing
code <- waitForProcess h
return $ code == ExitSuccess
isModelsimInstalled :: IO Bool
isModelsimInstalled = executablePresent "vlib" <&&>
executablePresent "vmap" <&&>
executablePresent "vcom" <&&>
executablePresent "vsim"
where executablePresent = (liftM (maybe False (\_-> True))) .findExecutable
(<&&>) :: Monad m => m Bool -> m Bool -> m Bool
x <&&> y = do p <- x
if p then y else return False