------------------------------------------------------------------------------- -- $Id: Simulation.hs#1 2009/10/01 10:31:09 REDMOND\\satnams $ ------------------------------------------------------------------------------- module Lava.Simulation where import Lava.TypeExpr ------------------------------------------------------------------------------- data TestVecs = TestVecs [SignalDec] [SignalDec] [[Stimulus]] deriving (Eq, Show) type SignalDec = (String, TypeExpr) data Stimulus = Bit Bool | BitV [Bool] | IntV Int deriving (Eq, Show) ------------------------------------------------------------------------------ truth_table :: Int -> [[Stimulus]] truth_table size = [map Bit (int2boolvec size n) | n <- [0..2^size-1]] ------------------------------------------------------------------------------- int2boolvec :: Int -> Int -> [Bool] int2boolvec 0 n | n > 0 = error "int2boolvec: size to small" int2boolvec 0 0 = [] int2boolvec n v = if v `mod` 2 == 0 then False : int2boolvec (n-1) (v `div` 2) else True : int2boolvec (n-1) (v `div` 2) ------------------------------------------------------------------------------- showBV :: [Bool] -> String showBV = map showBit . reverse ------------------------------------------------------------------------------- showBit :: Bool -> Char showBit False = '0' showBit True = '1' -------------------------------------------------------------------------------