Skip to content

Commit

Permalink
Use pre-whitespace position for source end locations
Browse files Browse the repository at this point in the history
Fixes #743
  • Loading branch information
expipiplus1 committed Oct 25, 2020
1 parent 820499d commit 731ed87
Showing 1 changed file with 15 additions and 9 deletions.
24 changes: 15 additions & 9 deletions src/Nix/Parser.hs
Original file line number Diff line number Diff line change
Expand Up @@ -53,13 +53,13 @@ import Control.Applicative hiding ( many
import Control.DeepSeq
import Control.Monad
import Control.Monad.Combinators.Expr
import Control.Monad.State.Strict
import Data.Char ( isAlpha
, isDigit
, isSpace
)
import Data.Data ( Data(..) )
import Data.Functor
import Data.Functor.Identity
import Data.HashSet ( HashSet )
import qualified Data.HashSet as HashSet
import Data.List.NonEmpty ( NonEmpty(..) )
Expand All @@ -81,7 +81,7 @@ import Nix.Render
import Prettyprinter ( Doc
, pretty
)
import Text.Megaparsec
import Text.Megaparsec hiding ( State )
import Text.Megaparsec.Char
import qualified Text.Megaparsec.Char.Lexer as L

Expand Down Expand Up @@ -439,7 +439,9 @@ skipLineComment' prefix = string prefix
*> void (takeWhileP (Just "character") (\x -> x /= '\n' && x /= '\r'))

whiteSpace :: Parser ()
whiteSpace = L.space space1 lineCmnt blockCmnt
whiteSpace = do
put =<< getSourcePos
L.space space1 lineCmnt blockCmnt
where
lineCmnt = skipLineComment' "#"
blockCmnt = L.skipBlockComment "/*" "*/"
Expand Down Expand Up @@ -513,20 +515,24 @@ reservedNames :: HashSet Text
reservedNames = HashSet.fromList
["let", "in", "if", "then", "else", "assert", "with", "rec", "inherit"]

type Parser = ParsecT Void Text Identity
type Parser = ParsecT Void Text (State SourcePos)

data Result a = Success a | Failure (Doc Void) deriving (Show, Functor)

parseFromFileEx :: MonadFile m => Parser a -> FilePath -> m (Result a)
parseFromFileEx p path = do
txt <- decodeUtf8 <$> readFile path
pure $ either (Failure . pretty . errorBundlePretty) Success $ parse p
path
txt
pure
$ either (Failure . pretty . errorBundlePretty) Success
. flip evalState (initialPos path)
$ runParserT p path txt

parseFromText :: Parser a -> Text -> Result a
parseFromText p txt =
either (Failure . pretty . errorBundlePretty) Success $ parse p "<string>" txt
let file = "<string>"
in either (Failure . pretty . errorBundlePretty) Success
. flip evalState (initialPos file)
$ runParserT p file txt

{- Parser.Operators -}

Expand All @@ -546,7 +552,7 @@ annotateLocation :: Parser a -> Parser (Ann SrcSpan a)
annotateLocation p = do
begin <- getSourcePos
res <- p
end <- getSourcePos
end <- get -- The state set before the last whitespace
pure $ Ann (SrcSpan begin end) res

annotateLocation1 :: Parser (NExprF NExprLoc) -> Parser NExprLoc
Expand Down

0 comments on commit 731ed87

Please sign in to comment.