Commit deed2d9f by Zachary Snow

enable PatternSynonyms and TupleSections everywhere

parent ba94920e
{-# LANGUAGE PatternSynonyms #-}
{- sv2v
- Author: Zachary Snow <zach@zachjs.com>
-
......
{-# LANGUAGE PatternSynonyms #-}
{- sv2v
- Author: Zachary Snow <zach@zachjs.com>
-
......
{-# LANGUAGE PatternSynonyms #-}
{- sv2v
- Author: Zachary Snow <zach@zachjs.com>
-
......
{-# LANGUAGE TupleSections #-}
{- sv2v
- Author: Zachary Snow <zach@zachjs.com>
-
......
{-# 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
......
{-# LANGUAGE PatternSynonyms #-}
{- sv2v
- Author: Zachary Snow <zach@zachjs.com>
-
......
{-# LANGUAGE PatternSynonyms #-}
{- sv2v
- Author: Zachary Snow <zach@zachjs.com>
-
......
{-# LANGUAGE TupleSections #-}
{- sv2v
- Author: Zachary Snow <zach@zachjs.com>
-
......
{-# LANGUAGE TupleSections #-}
{- sv2v
- Author: Zachary Snow <zach@zachjs.com>
-
......
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE TupleSections #-}
{- sv2v
- Author: Zachary Snow <zach@zachjs.com>
-
......
{-# LANGUAGE TupleSections #-}
{- sv2v
- Author: Zachary Snow <zach@zachjs.com>
-
......
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE FlexibleInstances #-}
{- sv2v
......
{-# LANGUAGE PatternSynonyms #-}
{- sv2v
- Author: Zachary Snow <zach@zachjs.com>
-
......
{-# LANGUAGE PatternSynonyms #-}
{- sv2v
- Author: Zachary Snow <zach@zachjs.com>
-
......
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE TupleSections #-}
{- sv2v
- Author: Zachary Snow <zach@zachjs.com>
-
......
{-# LANGUAGE PatternSynonyms #-}
{- sv2v
- Author: Zachary Snow <zach@zachjs.com>
-
......
{-# 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 $
......
{-# LANGUAGE PatternSynonyms #-}
{- sv2v
- Author: Zachary Snow <zach@zachjs.com>
- Initial Verilog AST Author: Tom Hawkins <tomahawkins@gmail.com>
......
{-# LANGUAGE PatternSynonyms #-}
{- sv2v
- Author: Zachary Snow <zach@zachjs.com>
- Initial Verilog AST Author: Tom Hawkins <tomahawkins@gmail.com>
......
{-# LANGUAGE PatternSynonyms #-}
{- sv2v
- Author: Zachary Snow <zach@zachjs.com>
- Initial Verilog AST Author: Tom Hawkins <tomahawkins@gmail.com>
......
{-# LANGUAGE PatternSynonyms #-}
{- sv2v
- Author: Zachary Snow <zach@zachjs.com>
- Initial Verilog AST Author: Tom Hawkins <tomahawkins@gmail.com>
......
{-# LANGUAGE TupleSections #-}
{- sv2v
- Author: Zachary Snow <zach@zachjs.com>
-
......
{-# LANGUAGE PatternSynonyms #-}
{- sv2v
- Author: Zachary Snow <zach@zachjs.com>
- Initial Verilog AST Author: Tom Hawkins <tomahawkins@gmail.com>
......
{-# 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
{-# 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
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment