mirror of https://github.com/zachjs/sv2v.git
enable PatternSynonyms and TupleSections everywhere
This commit is contained in:
parent
ba94920ee0
commit
deed2d9fc5
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE PatternSynonyms #-}
|
||||
{- sv2v
|
||||
- Author: Zachary Snow <zach@zachjs.com>
|
||||
-
|
||||
|
|
|
|||
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE PatternSynonyms #-}
|
||||
{- sv2v
|
||||
- Author: Zachary Snow <zach@zachjs.com>
|
||||
-
|
||||
|
|
|
|||
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE PatternSynonyms #-}
|
||||
{- sv2v
|
||||
- Author: Zachary Snow <zach@zachjs.com>
|
||||
-
|
||||
|
|
|
|||
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE TupleSections #-}
|
||||
{- sv2v
|
||||
- Author: Zachary Snow <zach@zachjs.com>
|
||||
-
|
||||
|
|
|
|||
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE PatternSynonyms #-}
|
||||
{- sv2v
|
||||
- Author: Zachary Snow <zach@zachjs.com>
|
||||
-
|
||||
|
|
|
|||
|
|
@ -43,8 +43,8 @@ convertExpr (Inside expr valueRanges) =
|
|||
BinOp LogAnd
|
||||
(BinOp Le lo expr)
|
||||
(BinOp Ge hi expr)
|
||||
toCheck pattern =
|
||||
BinOp WEq expr pattern
|
||||
toCheck pat =
|
||||
BinOp WEq expr pat
|
||||
convertExpr other = other
|
||||
|
||||
convertStmt :: Stmt -> Stmt
|
||||
|
|
|
|||
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE PatternSynonyms #-}
|
||||
{- sv2v
|
||||
- Author: Zachary Snow <zach@zachjs.com>
|
||||
-
|
||||
|
|
|
|||
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE PatternSynonyms #-}
|
||||
{- sv2v
|
||||
- Author: Zachary Snow <zach@zachjs.com>
|
||||
-
|
||||
|
|
|
|||
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE TupleSections #-}
|
||||
{- sv2v
|
||||
- Author: Zachary Snow <zach@zachjs.com>
|
||||
-
|
||||
|
|
|
|||
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE TupleSections #-}
|
||||
{- sv2v
|
||||
- Author: Zachary Snow <zach@zachjs.com>
|
||||
-
|
||||
|
|
|
|||
|
|
@ -1,5 +1,3 @@
|
|||
{-# LANGUAGE PatternSynonyms #-}
|
||||
{-# LANGUAGE TupleSections #-}
|
||||
{- sv2v
|
||||
- Author: Zachary Snow <zach@zachjs.com>
|
||||
-
|
||||
|
|
|
|||
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE TupleSections #-}
|
||||
{- sv2v
|
||||
- Author: Zachary Snow <zach@zachjs.com>
|
||||
-
|
||||
|
|
|
|||
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE TupleSections #-}
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
{- sv2v
|
||||
|
|
|
|||
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE PatternSynonyms #-}
|
||||
{- sv2v
|
||||
- Author: Zachary Snow <zach@zachjs.com>
|
||||
-
|
||||
|
|
|
|||
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE PatternSynonyms #-}
|
||||
{- sv2v
|
||||
- Author: Zachary Snow <zach@zachjs.com>
|
||||
-
|
||||
|
|
|
|||
|
|
@ -1,5 +1,3 @@
|
|||
{-# LANGUAGE PatternSynonyms #-}
|
||||
{-# LANGUAGE TupleSections #-}
|
||||
{- sv2v
|
||||
- Author: Zachary Snow <zach@zachjs.com>
|
||||
-
|
||||
|
|
|
|||
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE PatternSynonyms #-}
|
||||
{- sv2v
|
||||
- Author: Zachary Snow <zach@zachjs.com>
|
||||
-
|
||||
|
|
|
|||
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE PatternSynonyms #-}
|
||||
{- sv2v
|
||||
- Author: Zachary Snow <zach@zachjs.com>
|
||||
-
|
||||
|
|
|
|||
|
|
@ -76,10 +76,10 @@ convertExpr scopes (BinOp WEq l r) =
|
|||
BinOp BitAnd couldMatch $
|
||||
BinOp BitOr noExtraXZs $
|
||||
Number (Based 1 False Binary 0 1)
|
||||
else if numberToInteger pattern /= Nothing then
|
||||
else if numberToInteger pat /= Nothing then
|
||||
BinOp Eq l r
|
||||
else
|
||||
BinOp Eq (BinOp BitOr l mask) pattern'
|
||||
BinOp Eq (BinOp BitOr l mask) pat'
|
||||
where
|
||||
lxl = BinOp BitXor l l
|
||||
rxr = BinOp BitXor r r
|
||||
|
|
@ -92,10 +92,10 @@ convertExpr scopes (BinOp WEq l r) =
|
|||
lxlxrxr = BinOp BitXor lxl rxr
|
||||
-- For wildcard patterns we can find, use masking
|
||||
maybePattern = lookupPattern scopes r
|
||||
Just pattern = maybePattern
|
||||
Based size signed base vals knds = pattern
|
||||
Just pat = maybePattern
|
||||
Based size signed base vals knds = pat
|
||||
mask = Number $ Based size signed base knds 0
|
||||
pattern' = Number $ Based size signed base (vals .|. knds) 0
|
||||
pat' = Number $ Based size signed base (vals .|. knds) 0
|
||||
convertExpr scopes (BinOp WNe l r) =
|
||||
UniOp LogNot $
|
||||
convertExpr scopes $
|
||||
|
|
|
|||
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE PatternSynonyms #-}
|
||||
{- sv2v
|
||||
- Author: Zachary Snow <zach@zachjs.com>
|
||||
- Initial Verilog AST Author: Tom Hawkins <tomahawkins@gmail.com>
|
||||
|
|
|
|||
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE PatternSynonyms #-}
|
||||
{- sv2v
|
||||
- Author: Zachary Snow <zach@zachjs.com>
|
||||
- Initial Verilog AST Author: Tom Hawkins <tomahawkins@gmail.com>
|
||||
|
|
|
|||
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE PatternSynonyms #-}
|
||||
{- sv2v
|
||||
- Author: Zachary Snow <zach@zachjs.com>
|
||||
- Initial Verilog AST Author: Tom Hawkins <tomahawkins@gmail.com>
|
||||
|
|
|
|||
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE PatternSynonyms #-}
|
||||
{- sv2v
|
||||
- Author: Zachary Snow <zach@zachjs.com>
|
||||
- Initial Verilog AST Author: Tom Hawkins <tomahawkins@gmail.com>
|
||||
|
|
|
|||
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE TupleSections #-}
|
||||
{- sv2v
|
||||
- Author: Zachary Snow <zach@zachjs.com>
|
||||
-
|
||||
|
|
|
|||
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE PatternSynonyms #-}
|
||||
{- sv2v
|
||||
- Author: Zachary Snow <zach@zachjs.com>
|
||||
- Initial Verilog AST Author: Tom Hawkins <tomahawkins@gmail.com>
|
||||
|
|
|
|||
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE TupleSections #-}
|
||||
{- sv2v
|
||||
- Author: Zachary Snow <zach@zachjs.com>
|
||||
-}
|
||||
|
|
|
|||
|
|
@ -13,7 +13,6 @@
|
|||
-}
|
||||
{
|
||||
{-# LANGUAGE BlockArguments #-}
|
||||
{-# LANGUAGE TupleSections #-}
|
||||
module Language.SystemVerilog.Parser.Parse (parse) where
|
||||
|
||||
import Control.Monad.Except
|
||||
|
|
|
|||
|
|
@ -961,19 +961,19 @@ pushChars s p = mapM_ (flip pushChar p) s
|
|||
-- search for a pattern in the input and remove remove characters up to and
|
||||
-- including the first occurrence of the pattern
|
||||
removeThrough :: String -> PPS ()
|
||||
removeThrough pattern = do
|
||||
removeThrough pat = do
|
||||
str <- getInput
|
||||
case findIndex (isPrefixOf pattern) (tails str) of
|
||||
case findIndex (isPrefixOf pat) (tails str) of
|
||||
Nothing ->
|
||||
if pattern == "\n"
|
||||
if pat == "\n"
|
||||
then setInput ""
|
||||
else lexicalError $ "Reached EOF while looking for: "
|
||||
++ show pattern
|
||||
++ show pat
|
||||
Just patternIdx -> do
|
||||
let chars = patternIdx + length pattern
|
||||
let chars = patternIdx + length pat
|
||||
let (dropped, rest) = splitAt chars str
|
||||
advancePositions dropped
|
||||
when (pattern == "\n") $ do
|
||||
when (pat == "\n") $ do
|
||||
pos <- getPosition
|
||||
pushChar '\n' pos
|
||||
setInput rest
|
||||
|
|
|
|||
|
|
@ -1,4 +1,3 @@
|
|||
{-# LANGUAGE PatternSynonyms #-}
|
||||
{- sv2v
|
||||
- Author: Tom Hawkins <tomahawkins@gmail.com>
|
||||
- Modified by: Zachary Snow <zach@zachjs.com>
|
||||
|
|
|
|||
|
|
@ -120,6 +120,8 @@ executable sv2v
|
|||
autogen-modules:
|
||||
Paths_sv2v
|
||||
ghc-options:
|
||||
-XPatternSynonyms
|
||||
-XTupleSections
|
||||
-O3
|
||||
-threaded
|
||||
-rtsopts
|
||||
|
|
|
|||
Loading…
Reference in New Issue