now parsing memory statements

This commit is contained in:
Yehowshua Immanuel 2024-12-06 14:57:32 -05:00
parent cbbc7e73bd
commit 38fb13556f
6 changed files with 103 additions and 24 deletions

View file

@ -3,6 +3,7 @@ module Main where
import System.Environment (getArgs)
import System.IO
import Control.Exception (catch, IOException)
import Text.Show.Pretty (ppShow)
import Haskellator
@ -19,7 +20,7 @@ main = do
putStrLn "File Contents:"
putStrLn contents
[] -> putStrLn "cabal run Haskellator -- <file-path>"
putStrLn $ show Haskellator.val
putStrLn $ ppShow Haskellator.val
-- Handle potential file reading errors
handleReadError :: IOException -> IO String

View file

@ -5,8 +5,8 @@
- [x] <decimal-digit> ::= “0” | “1” | “2” | “3” | “4” | “5” | “6” | “7” | “8” | “9”
- [x] <binary-digit> ::= “0” | “1” | “x” | “z” | “m” | “-“
- [x] <integer> ::= “-“? <decimal-digit>+
- [ ] <file> ::= <autoidx-stmt>? <module>*
- [x] <autoidx-stmt> ::= “autoidx” <integer> <eol>
- [ ] <file> ::= <autoidx-stmt>? <module>*
- [ ] <module> ::= <attr-stmt>* <module-stmt> <module-body> <module-end-stmt>
- [x] <module-stmt> ::= “module” <id> <eol>
- [ ] <module-body> ::= (<param-stmt> | <wire> | <memory> | <cell> | <process> )*
@ -14,12 +14,12 @@
- [x] <constant> ::= <value> | <integer> | <string>
- [x] <module-end-stmt> ::= “end” <eol>
- [x] <attr-stmt> ::= “attribute” <id> <constant> <eol>
- [ ] <sigspec> ::= <constant> | <wire-id> | <sigspec> “[” <integer> (“:” <integer>)? “]” | “{” <sigspec>* “}”
- [ ] <conn-stmt> ::= “connect” <sigspec> <sigspec> <eol>
- [ ] <wire> ::= <attr-stmt>* <wire-stmt>
- [ ] <wire-stmt> ::= “wire” <wire-option>* <wire-id> <eol>
- [ ] <wire-id> ::= <id>
- [ ] <wire-option> ::= “width” <integer> | “offset” <integer> | “input” <integer> | “output” <integer> | “inout” <integer> | “upto” | “signed”
- [x] <sigspec> ::= <constant> | <wire-id> | <sigspec> “[” <integer> (“:” <integer>)? “]” | “{” <sigspec>* “}”
- [x] <conn-stmt> ::= “connect” <sigspec> <sigspec> <eol>
- [x] <wire> ::= <attr-stmt>* <wire-stmt>
- [x] <wire-stmt> ::= “wire” <wire-option>* <wire-id> <eol>
- [x] <wire-id> ::= <id>
- [x] <wire-option> ::= “width” <integer> | “offset” <integer> | “input” <integer> | “output” <integer> | “inout” <integer> | “upto” | “signed”
- [ ] <memory> ::= <attr-stmt>* <memory-stmt>
- [ ] <memory-stmt> ::= “memory” <memory-option>* <id> <eol>
- [ ] <memory-option> ::= “width” <integer> | “size” <integer> | “offset” <integer>

View file

@ -10,6 +10,7 @@ let
haskellPackages.filepath
haskellPackages.pretty-show
haskellPackages.prettyprinter
haskellPackages.pretty-show
];
in
haskellPackages.mkDerivation {

View file

@ -86,6 +86,7 @@ executable rtlil-parse
-- Other library packages from which modules are imported.
build-depends:
base ^>=4.17.2.1,
pretty-show >=1.6,
haskellator
-- Directories containing source files.

View file

@ -1,9 +1,12 @@
module RTLILParser.AST(
AutoIdxStmt(..), ParamStmt(..), AutogenId(..),
Constant(..), CellStmt(..), PublicId(..),
AttrStmt(..), Value(..), Id(..),
CellId(..), CellType(..), WireId(..),
SigSpec(..), Slice(..)
AutoIdxStmt(..) ,ParamStmt(..) ,AutogenId(..)
,Constant(..) ,CellStmt(..) ,PublicId(..)
,AttrStmt(..) ,Value(..) ,Id(..)
,CellId(..) ,CellType(..) ,WireId(..)
,SigSpec(..) ,Slice(..) ,ConnStmt(..)
,WireOption(..) ,WireStmt(..) ,Wire(..)
,MemoryOption(..) ,MemoryStmt(..) ,Memory(..)
,MemoryID(..)
) where
import Text.Read (Lexeme(Ident))
import Data.Functor.Contravariant (Contravariant)
@ -15,13 +18,30 @@ data Slice = Slice Int (Maybe Int) deriving (Show)
data Id = Public PublicId
| Autogen AutogenId
deriving (Show)
data WireId = WireId Id
deriving (Show)
data WireId = WireId Id deriving (Show)
data MemoryID = MemoryID Id deriving (Show)
data AutoIdxStmt = AutoIdxStmt Int deriving (Show)
data AttrStmt = AttrStmt Id Constant deriving (Show)
data CellStmt = CellStmt CellId CellType deriving (Show)
data CellId = CellId Id deriving (Show)
data CellType = CellType Id deriving (Show)
data AttrStmt = AttrStmt Id Constant deriving (Show)
data CellStmt = CellStmt CellId CellType deriving (Show)
data CellId = CellId Id deriving (Show)
data CellType = CellType Id deriving (Show)
data ConnStmt = ConnStmt SigSpec SigSpec deriving (Show)
data WireOption = WireOptionWidth Int
| WireOptionOffset Int
| WireOptionInput Int
| WireOptionOutput Int
| WireOptionInout Int
| WireOptionUpto
| WireOptionSigned
deriving (Show)
data WireStmt = WireStmt WireId [WireOption] deriving (Show)
data Wire = Wire WireStmt [AttrStmt] deriving (Show)
data MemoryOption = MemoryOptionWidth Int
| MemoryOptionSize Int
| MemoryOptionOffset Int
deriving (Show)
data MemoryStmt = MemoryStmt MemoryID [MemoryOption] deriving (Show)
data Memory = Memory MemoryStmt [AttrStmt] deriving (Show)
data SigSpec = SigSpecConstant Constant
| SigSpecWireId WireId
| SigSpecSlice SigSpec Slice

View file

@ -7,11 +7,14 @@ import Control.Monad (void)
import Text.Parsec
import Text.Parsec.String (Parser)
import RTLILParser.AST(
AutoIdxStmt(..), ParamStmt(..), AutogenId(..),
Constant(..), CellStmt(..), PublicId(..),
AttrStmt(..), Value(..), Id(..),
CellId(..), CellType(..), WireId(..),
SigSpec(..), Slice(..)
AutoIdxStmt(..) ,ParamStmt(..) ,AutogenId(..)
,Constant(..) ,CellStmt(..) ,PublicId(..)
,AttrStmt(..) ,Value(..) ,Id(..)
,CellId(..) ,CellType(..) ,WireId(..)
,SigSpec(..) ,Slice(..) ,ConnStmt(..)
,WireOption(..) ,WireStmt(..) ,Wire(..)
,MemoryOption(..) ,MemoryStmt(..) ,Memory(..)
,MemoryID(..)
)
import Util(binaryStringToInt)
import RTLILParser.Primitives(pEscapedChar)
@ -141,6 +144,59 @@ pSigSpec =
try pSigSpecConcat -- Check for concatenation first
<|> pSingleSigSpec -- Otherwise parse a single sigspec
pConnStmt :: Parser ConnStmt
pConnStmt = ConnStmt
<$> (string "connect" *> pWs *> pSigSpec)
<*> (pWs *> pSigSpec)
<* pEol
pWireOption :: Parser WireOption
pWireOption =
try (WireOptionWidth <$> (string "width" *> pWs *> pInteger)) <|>
try (WireOptionOffset <$> (string "offset" *> pWs *> pInteger)) <|>
try (WireOptionInput <$> (string "input" *> pWs *> pInteger)) <|>
try (WireOptionOutput <$> (string "output" *> pWs *> pInteger)) <|>
try (WireOptionInout <$> (string "inout" *> pWs *> pInteger)) <|>
(string "upto" *> return WireOptionUpto) <|>
(string "signed" *> return WireOptionSigned)
pWireStmt :: Parser WireStmt
pWireStmt =
WireStmt
<$ string "wire"
<* pWs
<*> (WireId <$> pId)
<* pWs
<*> many pWireOption
<* pEol
pWire :: Parser Wire
pWire = do
attrs <- many pAttrStmt
wireStmt <- pWireStmt
return $ Wire wireStmt attrs
pMemoryOption :: Parser MemoryOption
pMemoryOption =
try (MemoryOptionWidth <$> (string "width" *> pWs *> pInteger)) <|>
try (MemoryOptionSize <$> (string "size" *> pWs *> pInteger)) <|>
try (MemoryOptionOffset <$> (string "offset" *> pWs *> pInteger))
pMemoryStmt :: Parser MemoryStmt
pMemoryStmt =
MemoryStmt
<$ string "memory"
<* pWs
<*> (MemoryID <$> pId)
<* pWs
<*> many pMemoryOption
<* pEol
pMemory :: Parser Memory
pMemory = do
attrs <- many pAttrStmt
memoryStmt <- pMemoryStmt
return $ Memory memoryStmt attrs
-- would correspond to `123456789[0:9][0:8]`
exampleSigSpecSlice =