Commit d86f8535 by Zachary Snow

support for begin_keywords directive

parent 3d3359d3
{- sv2v
- Author: Zachary Snow <zach@zachjs.com>
-
- To implement the `begin_keywords` directive, this module defines which IEEE
- 1800-2017 keywords are not keywords in preceding specifications.
-}
module Language.SystemVerilog.Parser.Keywords
( specMap
) where
import qualified Data.Map.Strict as Map
import qualified Data.Set as Set
import Language.SystemVerilog.Parser.Tokens
newKeywords :: [(String, [TokenName])]
newKeywords = [
("1364-1995", [KW_always, KW_and, KW_assign, KW_begin, KW_buf, KW_bufif0,
KW_bufif1, KW_case, KW_casex, KW_casez, KW_cmos, KW_deassign, KW_default,
KW_defparam, KW_disable, KW_edge, KW_else, KW_end, KW_endcase,
KW_endfunction, KW_endmodule, KW_endprimitive, KW_endspecify, KW_endtable,
KW_endtask, KW_event, KW_for, KW_force, KW_forever, KW_fork, KW_function,
KW_highz0, KW_highz1, KW_if, KW_ifnone, KW_initial, KW_inout, KW_input,
KW_integer, KW_join, KW_large, KW_macromodule, KW_medium, KW_module,
KW_nand, KW_negedge, KW_nmos, KW_nor, KW_not, KW_notif0, KW_notif1, KW_or,
KW_output, KW_parameter, KW_pmos, KW_posedge, KW_primitive, KW_pull0,
KW_pull1, KW_pulldown, KW_pullup, KW_rcmos, KW_real, KW_realtime, KW_reg,
KW_release, KW_repeat, KW_rnmos, KW_rpmos, KW_rtran, KW_rtranif0,
KW_rtranif1, KW_scalared, KW_small, KW_specify, KW_specparam, KW_strong0,
KW_strong1, KW_supply0, KW_supply1, KW_table, KW_task, KW_time, KW_tran,
KW_tranif0, KW_tranif1, KW_tri, KW_tri0, KW_tri1, KW_triand, KW_trior,
KW_trireg, KW_vectored, KW_wait, KW_wand, KW_weak0, KW_weak1, KW_while,
KW_wire, KW_wor, KW_xnor, KW_xor]),
("1364-2001-noconfig", [KW_cell, KW_config, KW_design, KW_endconfig,
KW_incdir, KW_include, KW_instance, KW_liblist, KW_library, KW_use]),
("1364-2001", [KW_automatic, KW_endgenerate, KW_generate, KW_genvar,
KW_localparam, KW_noshowcancelled, KW_pulsestyle_ondetect,
KW_pulsestyle_onevent, KW_showcancelled, KW_signed, KW_unsigned]),
("1364-2005", [KW_uwire]),
("1800-2005", [KW_alias, KW_always_comb, KW_always_ff, KW_always_latch,
KW_assert, KW_assume, KW_before, KW_bind, KW_bins, KW_binsof, KW_bit,
KW_break, KW_byte, KW_chandle, KW_class, KW_clocking, KW_const,
KW_constraint, KW_context, KW_continue, KW_cover, KW_covergroup,
KW_coverpoint, KW_cross, KW_dist, KW_do, KW_endclass, KW_endclocking,
KW_endgroup, KW_endinterface, KW_endpackage, KW_endprogram, KW_endproperty,
KW_endsequence, KW_enum, KW_expect, KW_export, KW_extends, KW_extern,
KW_final, KW_first_match, KW_foreach, KW_forkjoin, KW_iff, KW_ignore_bins,
KW_illegal_bins, KW_import, KW_inside, KW_int, KW_interface, KW_intersect,
KW_join_any, KW_join_none, KW_local, KW_logic, KW_longint, KW_matches,
KW_modport, KW_new, KW_null, KW_package, KW_packed, KW_priority, KW_program,
KW_property, KW_protected, KW_pure, KW_rand, KW_randc, KW_randcase,
KW_randsequence, KW_ref, KW_return, KW_sequence, KW_shortint, KW_shortreal,
KW_solve, KW_static, KW_string, KW_struct, KW_super, KW_tagged, KW_this,
KW_throughout, KW_timeprecision, KW_timeunit, KW_type, KW_typedef, KW_union,
KW_unique, KW_var, KW_virtual, KW_void, KW_wait_order, KW_wildcard, KW_with,
KW_within]),
("1800-2009", [KW_accept_on, KW_checker, KW_endchecker, KW_eventually,
KW_global, KW_implies, KW_let, KW_nexttime, KW_reject_on, KW_restrict,
KW_s_always, KW_s_eventually, KW_s_nexttime, KW_s_until, KW_s_until_with,
KW_strong, KW_sync_accept_on, KW_sync_reject_on, KW_unique0, KW_until,
KW_until_with, KW_untyped, KW_weak]),
("1800-2012", [KW_implements, KW_nettype, KW_interconnect, KW_soft]),
("1800-2017", [])
]
specMap :: Map.Map String (Set.Set TokenName)
specMap =
Map.fromList $ zip keys vals
where
keys = map fst newKeywords
sets = map (Set.fromList . snd) newKeywords
allKeywords = Set.unions sets
vals =
map (Set.difference allKeywords) $
scanl1 Set.union sets
...@@ -33,9 +33,11 @@ import System.FilePath (dropFileName) ...@@ -33,9 +33,11 @@ import System.FilePath (dropFileName)
import System.Directory (findFile) import System.Directory (findFile)
import System.IO.Unsafe (unsafePerformIO) import System.IO.Unsafe (unsafePerformIO)
import qualified Data.Map.Strict as Map import qualified Data.Map.Strict as Map
import qualified Data.Set as Set
import Data.List (span, elemIndex, dropWhileEnd) import Data.List (span, elemIndex, dropWhileEnd)
import Data.Maybe (isJust, fromJust) import Data.Maybe (isJust, fromJust)
import Language.SystemVerilog.Parser.Keywords (specMap)
import Language.SystemVerilog.Parser.Tokens import Language.SystemVerilog.Parser.Tokens
} }
...@@ -513,13 +515,14 @@ data AlexUserState = LS ...@@ -513,13 +515,14 @@ data AlexUserState = LS
, lsEnv :: Env -- active macro definitions , lsEnv :: Env -- active macro definitions
, lsCondStack :: [Cond] -- if-else cascade state , lsCondStack :: [Cond] -- if-else cascade state
, lsIncludePaths :: [FilePath] -- folders to search for includes , lsIncludePaths :: [FilePath] -- folders to search for includes
, lsSpecStack :: [Set.Set TokenName] -- stack of non-keyword token names
} deriving (Eq, Show) } deriving (Eq, Show)
-- this initial user state does not contain the initial filename, environment, -- this initial user state does not contain the initial filename, environment,
-- or include paths; alex requires that this be defined; we override it before -- or include paths; alex requires that this be defined; we override it before
-- we begin the actual lexing procedure -- we begin the actual lexing procedure
alexInitUserState :: AlexUserState alexInitUserState :: AlexUserState
alexInitUserState = LS [] "" Map.empty [] [] alexInitUserState = LS [] "" Map.empty [] [] []
-- public-facing lexer entrypoint -- public-facing lexer entrypoint
lexFile :: [String] -> Env -> FilePath -> IO (Either String ([Token], Env)) lexFile :: [String] -> Env -> FilePath -> IO (Either String ([Token], Env))
...@@ -529,10 +532,14 @@ lexFile includePaths env path = do ...@@ -529,10 +532,14 @@ lexFile includePaths env path = do
return $ case result of return $ case result of
Left msg -> Left msg Left msg -> Left msg
Right finalState -> Right finalState ->
if null $ lsCondStack finalState if not $ null $ lsCondStack finalState then
then Right (finalToks, lsEnv finalState) Left $ path ++ ": unfinished conditional directives: " ++
else Left $ path ++ ": unfinished conditional directives: " ++ (show $ length $ lsCondStack finalState)
(show $ length $ lsCondStack finalState) else if not $ null $ lsSpecStack finalState then
Left $ path ++ ": unterminated begin_keywords blocks: " ++
(show $ length $ lsSpecStack finalState)
else
Right (finalToks, lsEnv finalState)
where finalToks = coalesce $ reverse $ lsToks finalState where finalToks = coalesce $ reverse $ lsToks finalState
where where
setEnv = do setEnv = do
...@@ -910,6 +917,27 @@ handleDirective (posOrig, _, _, strOrig) len = do ...@@ -910,6 +917,27 @@ handleDirective (posOrig, _, _, strOrig) len = do
"pragma" -> passThrough "pragma" -> passThrough
"resetall" -> passThrough "resetall" -> passThrough
"begin_keywords" -> do
quotedSpec <- takeQuotedString
let spec = tail $ init quotedSpec
case Map.lookup spec specMap of
Nothing ->
lexicalError $ "invalid keyword set name: " ++ show spec
Just set -> do
specStack <- gets lsSpecStack
modify $ \s -> s { lsSpecStack = set : specStack }
dropWhitespace
alexMonadScan
"end_keywords" -> do
specStack <- gets lsSpecStack
if null specStack
then
lexicalError "unexpected end_keywords before begin_keywords"
else do
modify $ \s -> s { lsSpecStack = tail specStack }
dropWhitespace
alexMonadScan
"__FILE__" -> do "__FILE__" -> do
tokPos <- toTokPos posOrig tokPos <- toTokPos posOrig
currFile <- gets lsCurrFile currFile <- gets lsCurrFile
...@@ -1070,7 +1098,11 @@ tok tokId (pos, _, _, input) len = do ...@@ -1070,7 +1098,11 @@ tok tokId (pos, _, _, input) len = do
tokPos <- toTokPos pos tokPos <- toTokPos pos
condStack <- gets lsCondStack condStack <- gets lsCondStack
() <- if any (/= CurrentlyTrue) condStack () <- if any (/= CurrentlyTrue) condStack
then modify id then return ()
else modify (push $ Token tokId tokStr tokPos) else do
specStack <- gets lsSpecStack
if null specStack || Set.notMember tokId (head specStack)
then modify (push $ Token tokId tokStr tokPos)
else modify (push $ Token Id_simple ('_' : tokStr) tokPos)
alexMonadScan alexMonadScan
} }
...@@ -381,4 +381,4 @@ data TokenName ...@@ -381,4 +381,4 @@ data TokenName
| Spe_Directive | Spe_Directive
| Unknown | Unknown
| MacroBoundary | MacroBoundary
deriving (Show, Eq) deriving (Show, Eq, Ord)
...@@ -48,6 +48,7 @@ executable sv2v ...@@ -48,6 +48,7 @@ executable sv2v
Language.SystemVerilog.AST.Stmt Language.SystemVerilog.AST.Stmt
Language.SystemVerilog.AST.Type Language.SystemVerilog.AST.Type
Language.SystemVerilog.Parser Language.SystemVerilog.Parser
Language.SystemVerilog.Parser.Keywords
Language.SystemVerilog.Parser.Lex Language.SystemVerilog.Parser.Lex
Language.SystemVerilog.Parser.Parse Language.SystemVerilog.Parser.Parse
Language.SystemVerilog.Parser.ParseDecl Language.SystemVerilog.Parser.ParseDecl
......
`begin_keywords "1364-2001-noconfig"
task foo;
integer automatic = 2;
$display(automatic * automatic);
endtask
`begin_keywords "1364-2005"
task automatic bar;
integer logic = 3;
$display(logic * logic);
endtask
`end_keywords
`end_keywords
module top;
initial foo;
initial bar;
endmodule
module top;
task foo;
integer x;
begin
x = 2;
$display(x * x);
end
endtask
task bar;
integer y;
begin
y = 3;
$display(y * y);
end
endtask
initial foo;
initial bar;
endmodule
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