verismith-1.1.0: Random verilog generation and simulator testing.
Copyright(c) 2018-2019 Yann Herklotz
LicenseGPL-3
Maintaineryann [at] yannherklotz [dot] com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Verismith.Tool.Internal

Description

Class of the simulator and the synthesize tool.

Synopsis

Documentation

type ResultSh = ResultT Failed Sh Source #

Type synonym for a ResultT that will be used throughout Verismith. This has instances for MonadSh and MonadIO if the Monad it is parametrised with also has those instances.

class Tool a where Source #

Tool class.

Methods

toText :: a -> Text Source #

Instances

Instances details
Tool SimTool Source # 
Instance details

Defined in Verismith.Report

Methods

toText :: SimTool -> Text Source #

Tool SynthTool Source # 
Instance details

Defined in Verismith.Report

Tool Icarus Source # 
Instance details

Defined in Verismith.Tool.Icarus

Methods

toText :: Icarus -> Text Source #

Tool Identity Source # 
Instance details

Defined in Verismith.Tool.Identity

Methods

toText :: Identity -> Text Source #

Tool Quartus Source # 
Instance details

Defined in Verismith.Tool.Quartus

Methods

toText :: Quartus -> Text Source #

Tool QuartusLight Source # 
Instance details

Defined in Verismith.Tool.QuartusLight

Tool Vivado Source # 
Instance details

Defined in Verismith.Tool.Vivado

Methods

toText :: Vivado -> Text Source #

Tool XST Source # 
Instance details

Defined in Verismith.Tool.XST

Methods

toText :: XST -> Text Source #

Tool Yosys Source # 
Instance details

Defined in Verismith.Tool.Yosys

Methods

toText :: Yosys -> Text Source #

class Tool a => Simulator a where Source #

Simulation type class.

Methods

runSim Source #

Arguments

:: Show ann 
=> a

Simulator instance

-> SourceInfo ann

Run information

-> [ByteString]

Inputs to simulate

-> ResultSh ByteString

Returns the value of the hash at the output of the testbench.

runSimWithFile :: a -> FilePath -> [ByteString] -> ResultSh ByteString Source #

class Tool a => Synthesiser a where Source #

Synthesiser type class.

Methods

runSynth Source #

Arguments

:: Show ann 
=> a

Synthesiser tool instance

-> SourceInfo ann

Run information

-> ResultSh ()

does not return any values

synthOutput :: a -> FilePath Source #

setSynthOutput :: a -> FilePath -> a Source #

Instances

Instances details
Synthesiser SynthTool Source # 
Instance details

Defined in Verismith.Report

Synthesiser Identity Source # 
Instance details

Defined in Verismith.Tool.Identity

Synthesiser Quartus Source # 
Instance details

Defined in Verismith.Tool.Quartus

Synthesiser QuartusLight Source # 
Instance details

Defined in Verismith.Tool.QuartusLight

Synthesiser Vivado Source # 
Instance details

Defined in Verismith.Tool.Vivado

Synthesiser XST Source # 
Instance details

Defined in Verismith.Tool.XST

Synthesiser Yosys Source # 
Instance details

Defined in Verismith.Tool.Yosys

data Failed Source #

Instances

Instances details
Monoid Failed Source # 
Instance details

Defined in Verismith.Tool.Internal

Semigroup Failed Source # 
Instance details

Defined in Verismith.Tool.Internal

Show Failed Source # 
Instance details

Defined in Verismith.Tool.Internal

Eq Failed Source # 
Instance details

Defined in Verismith.Tool.Internal

Methods

(==) :: Failed -> Failed -> Bool #

(/=) :: Failed -> Failed -> Bool #

checkPresentModules :: FilePath -> SourceInfo ann -> Sh [Text] Source #

Checks what modules are present in the synthesised output, as some modules may have been inlined. This could be improved if the parser worked properly.

replace :: FilePath -> Text -> Text -> Sh () Source #

Uses sed to replace a string in a text file.

replaceMods :: FilePath -> Text -> SourceInfo ann -> Sh () Source #

This is used because rename only renames the definitions of modules of course, so instead this just searches and replaces all the module names. This should find all the instantiations and definitions. This could again be made much simpler if the parser works.

bsToI :: ByteString -> Integer Source #

Helper function to convert bytestrings to integers

noPrint :: Sh a -> Sh a Source #

logger :: Text -> Sh () Source #

logCommand :: FilePath -> Text -> Sh a -> Sh a Source #

logCommand_ :: FilePath -> Text -> Sh a -> Sh () Source #

execute :: forall (m :: Type -> Type). (MonadSh m, Monad m) => Failed -> FilePath -> Text -> FilePath -> [Text] -> ResultT Failed m Text Source #

execute_ :: forall (m :: Type -> Type). (MonadSh m, Monad m) => Failed -> FilePath -> Text -> FilePath -> [Text] -> ResultT Failed m () Source #

(<?>) :: forall (m :: Type -> Type) a b. (Monad m, Monoid a) => ResultT a m b -> a -> ResultT a m b infix 0 Source #

annotate :: forall (m :: Type -> Type) a b. (Monad m, Monoid a) => a -> ResultT a m b -> ResultT a m b Source #