{-# LANGUAGE DeriveDataTypeable #-}
module Update.Span
( SpanUpdate(..)
, SrcSpan(..)
, SourcePos(..)
, updateSpan
, updateSpans
, linearizeSourcePos
, prettyPrintSourcePos
, split
) where
import Control.Exception (assert)
import Data.Data (Data)
import Data.Int (Int64)
import Data.List (genericTake, sortOn)
import Data.Text (Text, length, lines, splitAt)
import Prelude hiding (length, lines, splitAt)
import Nix.Expr.Types.Annotated
data SpanUpdate = SpanUpdate{ spanUpdateSpan :: SrcSpan
, spanUpdateContents :: Text
}
deriving (Show, Data)
updateSpans :: [SpanUpdate] -> Text -> Text
updateSpans us t =
let sortedSpans = sortOn (spanBegin . spanUpdateSpan) us
anyOverlap = any (uncurry overlaps)
(zip <*> tail $ spanUpdateSpan <$> sortedSpans)
in
assert (not anyOverlap)
(foldr updateSpan t sortedSpans)
updateSpan :: SpanUpdate -> Text -> Text
updateSpan (SpanUpdate (SrcSpan b e) r) t =
let (before, _) = split b t
(_, end) = split e t
in before <> r <> end
overlaps :: SrcSpan -> SrcSpan -> Bool
overlaps (SrcSpan b1 e1) (SrcSpan b2 e2) =
b2 >= b1 && b2 < e1 || e2 >= b1 && e2 < e1
split :: SourcePos -> Text -> (Text, Text)
split (SourcePos _ row col) t = splitAt
(fromIntegral
(linearizeSourcePos t (fromIntegral (unPos row - 1)) (fromIntegral (unPos col - 1)))
)
t
linearizeSourcePos :: Text
-> Int64
-> Int64
-> Int64
linearizeSourcePos t l c = fromIntegral lineCharOffset + c
where lineCharOffset = sum . fmap ((+1) . length) . genericTake l . lines $ t
prettyPrintSourcePos :: SourcePos -> String
prettyPrintSourcePos (SourcePos _ row column) =
"line " <> show row <> " column " <> show column