Skip to content

Commit

Permalink
fileLocs
Browse files Browse the repository at this point in the history
  • Loading branch information
janmasrovira committed Jan 7, 2025
1 parent 1e8568b commit 06d8b93
Show file tree
Hide file tree
Showing 2 changed files with 32 additions and 8 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -48,14 +48,7 @@ scanner fp bs = do
return ScanResult {..}
where
allFileLocs :: [FileLoc]
allFileLocs =
[ FileLoc
{ _locLine = Pos (1 + fromIntegral l),
_locCol = Pos (1 + fromIntegral c),
_locOffset = Pos (fromIntegral p)
}
| (FP.Pos p, (l, c)) <- zipExact importsPositions (posLineCols bs importsPositions)
]
allFileLocs = fileLocs bs importsPositions

importsPositions :: [FP.Pos]
importsPositions = concatMap spanToPos importsSpans
Expand Down
31 changes: 31 additions & 0 deletions src/Juvix/Prelude/FlatParse.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,10 +2,41 @@ module Juvix.Prelude.FlatParse
( module FlatParse.Basic,
module Control.Monad.Combinators,
module Data.ByteString,
module Juvix.Prelude.FlatParse,
)
where

import Control.Monad.Combinators (manyTill_, sepBy1)
import Data.ByteString (ByteString)
import FlatParse.Basic hiding (some, (<|>))
import Juvix.Data.Loc qualified as Loc
import Juvix.Prelude.Base

-- | It assumes all given positions are valid in the given bytestring
fileLocs :: ByteString -> [Pos] -> [Loc.FileLoc]
fileLocs bs positions =
let go :: Loc.Pos -> Loc.Pos -> Loc.Pos -> [(Int, Pos)] -> Parser Void [(Int, Loc.FileLoc)]
go !line !col !offset = \case
[] -> pure []
allPos@((i, pos) : poss) -> do
p <- getPos
let fl =
Loc.FileLoc
{ _locLine = line,
_locCol = col,
_locOffset = offset
}
if
| pos == p -> ((i, fl) :) <$> go line col offset poss
| otherwise ->
do
c <- anyChar
if
| '\n' == c -> go (line + 1) 1 (succ offset) allPos
| otherwise -> go line (col + 1) (succ offset) allPos

sorted :: [(Int, Pos)]
sorted = sortBy (\(_, i) (_, j) -> compare i j) (zip [0 ..] positions)
in case runParser (go 1 1 0 sorted) bs of
OK res _ -> snd <$> sortOn fst res
_ -> error "FlatParse.fileLocs: invalid position"

0 comments on commit 06d8b93

Please sign in to comment.