now parsing sigspec

This commit is contained in:
Yehowshua Immanuel 2024-12-06 12:15:33 -05:00
parent adc7511ca9
commit cbbc7e73bd
3 changed files with 61 additions and 16 deletions

View file

@ -46,7 +46,7 @@ AST for the given input `il` file.
```bash ```bash
$ nix-shell $ nix-shell
$ rtlil-parse test/corpus/xprop_dffe_1nnd_wrapped_xprop.il -o parsed1.ast $ rtlil-parse
``` ```
# TODO # TODO

View file

@ -1,9 +1,9 @@
module RTLILParser.AST( module RTLILParser.AST(
AutoIdxStmt(..), ParamStmt(..), AutogenId(..), AutoIdxStmt(..), ParamStmt(..), AutogenId(..),
Constant(..), CellStmt(..), PublicId(..), Constant(..), CellStmt(..), PublicId(..),
AttrStmt(..), Value(..), Id(..), AttrStmt(..), Value(..), Id(..),
CellId(..), CellType(..), WireId(..), CellId(..), CellType(..), WireId(..),
SigSpec(..) SigSpec(..), Slice(..)
) where ) where
import Text.Read (Lexeme(Ident)) import Text.Read (Lexeme(Ident))
import Data.Functor.Contravariant (Contravariant) import Data.Functor.Contravariant (Contravariant)
@ -11,6 +11,7 @@ import GHC.RTS.Flags (DoCostCentres(CostCentresAll))
data PublicId = PublicId String deriving (Show) data PublicId = PublicId String deriving (Show)
data AutogenId = AutogenId String deriving (Show) data AutogenId = AutogenId String deriving (Show)
data Slice = Slice Int (Maybe Int) deriving (Show)
data Id = Public PublicId data Id = Public PublicId
| Autogen AutogenId | Autogen AutogenId
deriving (Show) deriving (Show)
@ -23,7 +24,7 @@ data CellId = CellId Id deriving (Show)
data CellType = CellType Id deriving (Show) data CellType = CellType Id deriving (Show)
data SigSpec = SigSpecConstant Constant data SigSpec = SigSpecConstant Constant
| SigSpecWireId WireId | SigSpecWireId WireId
| SigSpecSlice SigSpec Int (Maybe Int) | SigSpecSlice SigSpec Slice
| SigSpecConcat [SigSpec] | SigSpecConcat [SigSpec]
deriving (Show) deriving (Show)
data Value = Value data Value = Value

View file

@ -1,5 +1,5 @@
-- this parser largely references: -- this parser largely references:
-- https://github.com/YosysHQ/yosys/blob/111b747d2797238eadf541879848492a9d34909a/docs/source/yosys_internals/formats/rtlil_text.rst -- https://yosyshq.readthedocs.io/projects/yosys/en/stable/appendix/rtlil_text.html
module RTLILParser.Parser(a, val) where module RTLILParser.Parser(a, val) where
@ -7,11 +7,11 @@ import Control.Monad (void)
import Text.Parsec import Text.Parsec
import Text.Parsec.String (Parser) import Text.Parsec.String (Parser)
import RTLILParser.AST( import RTLILParser.AST(
AutoIdxStmt(..), ParamStmt(..), AutogenId(..), AutoIdxStmt(..), ParamStmt(..), AutogenId(..),
Constant(..), CellStmt(..), PublicId(..), Constant(..), CellStmt(..), PublicId(..),
AttrStmt(..), Value(..), Id(..), AttrStmt(..), Value(..), Id(..),
CellId(..), CellType(..), WireId(..), CellId(..), CellType(..), WireId(..),
SigSpec(..) SigSpec(..), Slice(..)
) )
import Util(binaryStringToInt) import Util(binaryStringToInt)
import RTLILParser.Primitives(pEscapedChar) import RTLILParser.Primitives(pEscapedChar)
@ -20,6 +20,9 @@ import RTLILParser.Primitives(pEscapedChar)
nonws :: Parser Char nonws :: Parser Char
nonws = noneOf " \t\r\n" nonws = noneOf " \t\r\n"
pMaybeWs :: Parser String
pMaybeWs = many (oneOf " \t")
pWs :: Parser String pWs :: Parser String
pWs = many1 (oneOf " \t") pWs = many1 (oneOf " \t")
@ -105,12 +108,53 @@ pCellStmt = do
_ <- pEol _ <- pEol
return $ CellStmt cellId cellType return $ CellStmt cellId cellType
-- Parse a single slice
pSlice :: Parser Slice
pSlice =
Slice
<$> (char '[' *> pMaybeWs *> pInteger <* pMaybeWs)
<*> (optionMaybe (char ':' *> pInteger) <* pMaybeWs <* char ']')
-- pModuleStmt :: Parser () pSigSpecConcat :: Parser SigSpec
-- pModuleStmt = pSigSpecConcat = do
_ <- char '{' <* pWs
sigspecs <- pSigSpec `sepBy` pWs
_ <- pWs <* char '}'
return $ SigSpecConcat sigspecs
applySlices :: SigSpec -> Parser SigSpec
applySlices base = do
maybeSlice <- optionMaybe pSlice
case maybeSlice of
Nothing -> return base
Just slice -> applySlices (SigSpecSlice base slice)
pSingleSigSpec :: Parser SigSpec
pSingleSigSpec = do
baseSigSpec <- (SigSpecConstant <$> pConstant)
<|>
(SigSpecWireId <$> pWireId)
applySlices baseSigSpec
pSigSpec :: Parser SigSpec
pSigSpec =
try pSigSpecConcat -- Check for concatenation first
<|> pSingleSigSpec -- Otherwise parse a single sigspec
-- would correspond to `123456789[0:9][0:8]`
exampleSigSpecSlice =
SigSpecSlice
(
SigSpecSlice
(SigSpecConstant (ConstantInteger 123456789))
(Slice 0 $ Just 9)
)
(Slice 0 $ Just 8)
-- val = parse pInteger "pInteger" "721" -- val = parse pInteger "pInteger" "721"
val = parse pModuleStmt "pModuleStmt" "module \\top\n" -- val = parse pModuleStmt "pModuleStmt" "module \\top\n"
val = parse pSigSpec "pSigSpecSlice" "123456789[0:9][0:8]"
a :: Int a :: Int
a = 3 a = 3