module ForSyDe.Deep.Backend.VHDL.Ghdl (executeTestBenchGhdl) 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.Maybe (isJust)
import Control.Monad.State (gets)
import System.Directory (findExecutable,
setCurrentDirectory,
getTemporaryDirectory,
createDirectoryIfMissing)
import System.Process (readProcessWithExitCode, readProcess, runProcess, waitForProcess)
import System.Exit (ExitCode(..))
import System.IO
import System.FilePath ((</>))
import qualified Language.Haskell.TH as TH (Exp)
data GhdlCommand = Analyze | Elaborate | Compile | Import | Run deriving Eq
instance Show GhdlCommand where
show Analyze = "-a"
show Elaborate = "-e"
show Compile = "-c"
show Import = "-i"
show Run = "-r"
data GhdlEnv = GhdlEnv { sysId :: String
, sysTb :: String
, syslib :: String
, tbFile :: FilePath
, tbExecutable :: FilePath
, libFile :: FilePath
, workFiles :: [FilePath]
, forsydeLibFile :: FilePath
, forsydeLibDir :: FilePath
, systemLibDir :: FilePath
, workDir :: FilePath
, paths :: [FilePath]
}
mkGhdlEnv :: SysDefVal -> FilePath -> GhdlEnv
mkGhdlEnv sys osDataPath =
GhdlEnv
{ sysId = sysId
, sysTb = sysTb
, syslib = syslib
, libFile = syslib </> (syslib ++ ".vhd")
, tbFile = "test" </> (sysTb ++ ".vhd")
, forsydeLibFile = osDataPath</>"lib"</>"forsyde.vhd"
, workFiles = ("work" </> (sysId ++ ".vhd")) :
map (("work"</>).(++".vhd").sid.readURef.unPrimSysDef)
(subSys sys)
, forsydeLibDir = forsydeLibDir
, systemLibDir = systemLibDir
, workDir = workDir
, tbExecutable = workDir </> sysTb
, paths = [forsydeLibDir, systemLibDir, workDir]
}
where
sysId = sid sys
syslib = sysId ++ "_lib"
sysTb = sysId ++ "_tb"
workDir = "work" </> "ghdl"
forsydeLibDir = "forsyde" </> "ghdl"
systemLibDir = syslib </> "ghdl"
executeTestBenchGhdl :: Maybe Int
-> [[TH.Exp]]
-> VHDLM [[String]]
executeTestBenchGhdl mCycles stimuli = do
installed <- liftIO isGhdlInstalled
unless installed (throwFError GhdlFailed)
cycles <- writeVHDLTestBench mCycles stimuli
sysid <- gets (sid.globalSysDef.global)
sys <- gets (globalSysDef.global)
dataPath <- liftIO getDataDir
let env = mkGhdlEnv sys dataPath
file <- liftIO $ do
setCurrentDirectory (sysid </> "vhdl")
tmpdir <- getTemporaryDirectory
(file, handle) <- openTempFile tmpdir "tb_out.txt"
hClose handle
mapM_ (createDirectoryIfMissing True) $ paths env
return file
runGhdlCommand Analyze "forsyde"
(forsydeLibDir env)
[]
[forsydeLibFile env]
runGhdlCommand Analyze (syslib env)
(systemLibDir env)
[forsydeLibDir env]
[libFile env]
runGhdlCompile (sysTb env)
(workDir env)
[forsydeLibDir env, systemLibDir env]
(tbFile env:workFiles env)
testOutput <- runGhdlSim (sysTb env) cycles
liftIO $ setCurrentDirectory (".." </> "..")
parseTestBenchOut testOutput
runGhdlCompile :: String -> FilePath -> [FilePath] -> [FilePath] -> VHDLM ()
runGhdlCompile toplevel workdir libPaths files =
runGhdlCommandInWorkdir Compile "work" workdir libPaths files extra
where
extra = [show Elaborate,
toplevel]
runGhdlCommand :: GhdlCommand
-> String -> FilePath -> [FilePath] -> [FilePath]
-> VHDLM ()
runGhdlCommand cmd lib work paths files =
runGhdlCommandInWorkdir cmd lib work paths files []
runGhdlCommandInWorkdir :: GhdlCommand
-> String -> FilePath -> [FilePath] -> [FilePath]
-> [String]
-> VHDLM ()
runGhdlCommandInWorkdir command libName workdir libPaths files extraOpts =
runCommand "ghdl" $ cmd ++ paths ++ opts ++ files ++ extraOpts
where
cmd = [show command]
paths = map ("-P"++) libPaths
opts = ["--work="++libName,
"--workdir="++workdir]
runGhdlSim :: String -> Int -> VHDLM String
runGhdlSim toplevel cycles = do
(output,success) <- liftIO $ do
putStrLn $ "Running: ghdl " ++ unwords args
(exitcode,stdout,stderr) <- readProcessWithExitCode "ghdl" args stdin
let success = exitcode == ExitSuccess
return (stdout,success)
unless success (throwFError GhdlFailed)
return output
where
stdin = ""
args = [show Run, toplevel, "--stop-time="++show (cycles*10)++"ns"]
runCommand :: String
-> [String]
-> VHDLM ()
runCommand command args = do
success <- liftIO $ do
putStrLn msg
h <- runProcess command args Nothing Nothing Nothing Nothing Nothing
code <- waitForProcess h
return $ code == ExitSuccess
unless success (throwFError GhdlFailed)
where msg = "Running: " ++ command ++ " " ++ unwords args
isGhdlInstalled :: IO Bool
isGhdlInstalled = executablePresent "ghdl"
where executablePresent = liftM isJust .findExecutable