Skip to content
GitLab
Projects
Groups
Snippets
Help
Loading...
Help
What's new
10
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
Open sidebar
Glasgow Haskell Compiler
GHC
Commits
b017f34b
Commit
b017f34b
authored
Jul 06, 2010
by
Ian Lynagh
Browse files
Options
Browse Files
Download
Email Patches
Plain Diff
Make mkPState and pragState take their arguments in the same order
parent
fb853543
Changes
4
Hide whitespace changes
Inline
Side-by-side
Showing
4 changed files
with
8 additions
and
7 deletions
+8
-7
compiler/cmm/CmmParse.y
compiler/cmm/CmmParse.y
+1
-1
compiler/main/HeaderInfo.hs
compiler/main/HeaderInfo.hs
+1
-1
compiler/main/HscMain.lhs
compiler/main/HscMain.lhs
+2
-2
compiler/parser/Lexer.x
compiler/parser/Lexer.x
+4
-3
No files found.
compiler/cmm/CmmParse.y
View file @
b017f34b
...
...
@@ -1033,7 +1033,7 @@ parseCmmFile dflags filename = do
buf <- hGetStringBuffer filename
let
init_loc = mkSrcLoc (mkFastString filename) 1 1
init_state = (mkPState buf init_loc
dflags
) { lex_state = [0] }
init_state = (mkPState
dflags
buf init_loc) { lex_state = [0] }
-- reset the lex_state: the Lexer monad leaves some stuff
-- in there we don't want.
case unP cmmParse init_state of
...
...
compiler/main/HeaderInfo.hs
View file @
b017f34b
...
...
@@ -57,7 +57,7 @@ getImports :: GhcMonad m =>
-- ^ The source imports, normal imports, and the module name.
getImports
dflags
buf
filename
source_filename
=
do
let
loc
=
mkSrcLoc
(
mkFastString
filename
)
1
1
case
unP
parseHeader
(
mkPState
buf
loc
dflags
)
of
case
unP
parseHeader
(
mkPState
dflags
buf
loc
)
of
PFailed
span
err
->
parseError
span
err
POk
pst
rdr_module
->
do
let
_ms
@
(
_warns
,
errs
)
=
getMessages
pst
...
...
compiler/main/HscMain.lhs
View file @
b017f34b
...
...
@@ -186,7 +186,7 @@ hscParse mod_summary = do
let loc = mkSrcLoc (mkFastString src_filename) 1 1
case unP parseModule (mkPState buf loc
dflags
) of
case unP parseModule (mkPState
dflags
buf loc) of
PFailed span err ->
throwOneError (mkPlainErrMsg span err)
...
...
@@ -996,7 +996,7 @@ hscParseThing parser dflags str
let loc = mkSrcLoc (fsLit "<interactive>") 1 1
case unP parser (mkPState buf loc
dflags
) of
case unP parser (mkPState
dflags
buf loc) of
PFailed span err -> do
let msg = mkPlainErrMsg span err
...
...
compiler/parser/Lexer.x
View file @
b017f34b
...
...
@@ -1816,8 +1816,8 @@ pragState dynflags buf loc =
-- create a parse state
--
mkPState :: StringBuffer -> SrcLoc ->
DynFlags ->
PState
mkPState buf loc
flags =
mkPState ::
DynFlags ->
StringBuffer -> SrcLoc -> PState
mkPState
flags
buf loc
=
PState {
buffer = buf,
dflags = flags,
...
...
@@ -2201,7 +2201,8 @@ reportLexError loc1 loc2 buf str
lexTokenStream :: StringBuffer -> SrcLoc -> DynFlags -> ParseResult [Located Token]
lexTokenStream buf loc dflags = unP go initState
where initState = mkPState buf loc (dopt_set (dopt_unset dflags Opt_Haddock) Opt_KeepRawTokenStream)
where dflags' = dopt_set (dopt_unset dflags Opt_Haddock) Opt_KeepRawTokenStream
initState = mkPState dflags' buf loc
go = do
ltok <- lexer return
case ltok of
...
...
Write
Preview
Markdown
is supported
0%
Try again
or
attach a new file
.
Attach a file
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Cancel
Please
register
or
sign in
to comment