kansas-lava-0.2.4.5: Kansas Lava is a hardware simulator and VHDL generator.

Safe HaskellNone
LanguageHaskell2010

Language.KansasLava.Test

Synopsis

Documentation

verbose :: Int -> String -> Int -> String -> IO () Source #

fileReporter :: FilePath -> FilePath -> Result -> IO () Source #

data TestSeq Source #

Constructors

TestSeq (String -> Int -> Fabric () -> Fabric (Int -> Maybe String) -> IO ()) () 

testFabrics Source #

Arguments

:: Options 
-> SimMods
(String,KLEG -> IO KLEG)
-> String 
-> Int 
-> Fabric () 
-> Fabric (Int -> Maybe String) 
-> IO () 

data Gen a Source #

Constructors

Gen Integer (Integer -> Maybe a) 

arbitrary :: forall w. Rep w => Gen w Source #

allCases :: Rep w => [w] Source #

allCases returns all values of type w, in a non-random order.

finiteCases :: Rep w => Int -> [w] Source #

finiteCases returns finite values, perhaps many times, in a random order.

testDriver :: Options -> [TestSeq -> IO ()] -> IO () Source #

data Options Source #

Constructors

Options 

Fields

  • genSim :: Bool

    Generate modelsim testbenches for each test?

  • runSim :: Bool

    Run the tests after generation?

  • simCmd :: String

    Command to call with runSim is True

  • simPath :: FilePath

    Path into which we place all our simulation directories.

  • permuteMods :: Bool

    False: Run each mod separately. True: Run all possible permutations of the mods to see if they affect each other.

  • verboseOpt :: Int

    See verbose table below.

  • testOnly :: Maybe [String]

    Lists of tests to execute. Can match either end. Nothing means all tests.

  • testNever :: [String]

    List of tests to never execute. Can match either end.

  • testData :: Int

    cut off for random testing

  • parTest :: Int

    how may tests to run in parallel

Instances

Data Options Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Options -> c Options #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Options #

toConstr :: Options -> Constr #

dataTypeOf :: Options -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Options) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Options) #

gmapT :: (forall b. Data b => b -> b) -> Options -> Options #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Options -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Options -> r #

gmapQ :: (forall d. Data d => d -> u) -> Options -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Options -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Options -> m Options #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Options -> m Options #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Options -> m Options #

Show Options Source # 
Default Options Source # 

Methods

def :: Options #

matchExpected :: (Rep a, Size (W a), Show a) => String -> Seq a -> Fabric (Int -> Maybe String) Source #

matchExpected reads a named input port from a Fabric, and checks to see that it is a refinement of a given "specification" of the output. If there is a problem, issue an error message.

testStream :: forall w1 w2. (Eq w1, Rep w1, Show w1, Size (W w1), Eq w2, Rep w2, Show w2, Size (W w2)) => TestSeq -> String -> StreamTest w1 w2 -> IO () Source #