Copyright | (C) 2019 Google Inc. 2022 QBayLogic B.V. |
---|---|
License | BSD2 (see the file LICENSE) |
Maintainer | QBayLogic B.V. <devops@qbaylogic.com> |
Safe Haskell | None |
Language | Haskell2010 |
I/O actions that are translatable to HDL
Synopsis
- mealyIO :: KnownDomain dom => Clock dom -> (s -> i -> SimIO o) -> SimIO s -> Signal dom i -> Signal dom o
- data SimIO a
- display :: String -> SimIO ()
- finish :: Integer -> SimIO a
- data Reg a
- reg :: a -> SimIO (Reg a)
- readReg :: Reg a -> SimIO a
- writeReg :: Reg a -> a -> SimIO ()
- data File
- openFile :: FilePath -> String -> SimIO File
- closeFile :: File -> SimIO ()
- getChar :: File -> SimIO Char
- putChar :: Char -> File -> SimIO ()
- getLine :: forall n. KnownNat n => File -> Reg (Vec n (Unsigned 8)) -> SimIO Int
- isEOF :: File -> SimIO Bool
- flush :: File -> SimIO ()
- seek :: File -> Integer -> Int -> SimIO Int
- rewind :: File -> SimIO Int
- tell :: File -> SimIO Integer
I/O environment for simulation
:: KnownDomain dom | |
=> Clock dom | Clock at which rate the I/O environment progresses |
-> (s -> i -> SimIO o) | Transition function inside an I/O environment |
-> SimIO s | I/O action to create the initial state |
-> Signal dom i | |
-> Signal dom o |
Simulation-level I/O environment that can be synthesized to HDL-level I/O. Note that it is unlikely that the HDL-level I/O can subsequently be synthesized to a circuit.
Example
tbMachine :: (File,File) -> Int -> SimIO Int tbMachine (fileIn,fileOut) regOut = do eofFileOut <-isEOF
fileOut eofFileIn <-isEOF
fileIn when (eofFileIn || eofFileOut) $ dodisplay
"success"finish
0 goldenIn <-getChar
fileIn goldenOut <-getChar
fileOut res <- if regOut == fromEnum goldenOut then do return (fromEnum goldenIn) else dodisplay
"Output doesn't match golden output"finish
1 display ("Output matches golden output") return res tbInit :: (File,File) tbInit = do fileIn <-openFile
"./goldenInput00.txt" "r" fileOut <-openFile
"./goldenOutput00.txt" "r" return (fileIn,fileOut) topEntity :: Signal System Int topEntity = regOut where clk = systemClockGen rst = resetGen ena = enableGen regOut = register clk rst ena (fromEnum 'a') regIn regIn =mealyIO
clk tbMachine tbInit regOut
Simulation-level I/O environment; synthesizable to HDL I/O, which in itself is unlikely to be synthesisable to a digital circuit.
See mealyIO
as to its use.
Display on stdout
End of simulation
Finish the simulation with an exit code
Mutable values
Create a new mutable reference with the given starting value
Write new value to the mutable reference
File I/O
:: FilePath | File to open |
-> String | File mode:
|
-> SimIO File |
Open a file
Reading and writing characters
Insert a character into a buffer specified by the file
Reading strings
:: forall n. KnownNat n | |
=> File | File to read from |
-> Reg (Vec n (Unsigned 8)) | Vector to store the content |
-> SimIO Int |
Read one line from a file
Detecting the end of input
Determine whether we've reached the end of the file
Buffering operations
Repositioning handles
:: File | File to set the position for |
-> Integer | Position |
-> Int | Mode:
|
-> SimIO Int |
Set the position of the next operation on the file