diff --git a/src/Data/Source.hs b/src/Data/Source.hs index 4ec30c708..deadfccdb 100644 --- a/src/Data/Source.hs +++ b/src/Data/Source.hs @@ -11,7 +11,7 @@ import Prologue import Test.LeanCheck -- | The contents of a source file, represented as a ByteString. -newtype Source = Source { sourceText :: B.ByteString } +newtype Source = Source { sourceBytes :: B.ByteString } deriving (Eq, IsString, Show) @@ -26,16 +26,16 @@ slice range = take . drop take = Data.Source.take (rangeLength range) drop :: Int -> Source -> Source -drop i = Source . drop . sourceText +drop i = Source . drop . sourceBytes where drop = B.drop i take :: Int -> Source -> Source -take i = Source . take . sourceText +take i = Source . take . sourceBytes where take = B.take i -- | Return the ByteString contained in the 'Source'. toText :: Source -> Text -toText = decodeUtf8 . sourceText +toText = decodeUtf8 . sourceBytes -- | Split the source into the longest prefix of elements that do not satisfy the predicate and the rest without copying. break :: (Word8 -> Bool) -> Source -> (Source, Source) @@ -43,7 +43,7 @@ break predicate (Source text) = let (start, remainder) = B.break predicate text -- | Split the contents of the source after newlines. actualLines :: Source -> [Source] -actualLines = fmap Source . actualLines' . sourceText +actualLines = fmap Source . actualLines' . sourceBytes where actualLines' text | B.null text = [ text ] | otherwise = case B.break (== toEnum (fromEnum '\n')) text of @@ -54,12 +54,12 @@ actualLines = fmap Source . actualLines' . sourceText -- | Compute the 'Range's of each line in a 'Source'. actualLineRanges :: Source -> [Range] actualLineRanges = Prologue.drop 1 . scanl toRange (Range 0 0) . actualLines - where toRange previous string = Range (end previous) $ end previous + B.length (sourceText string) + where toRange previous source = Range (end previous) $ end previous + sourceLength source -- | Compute the 'Range's of each line in a 'Range' of a 'Source'. actualLineRangesWithin :: Range -> Source -> [Range] actualLineRangesWithin range = Prologue.drop 1 . scanl toRange (Range (start range) (start range)) . actualLines . slice range - where toRange previous string = Range (end previous) $ end previous + B.length (sourceText string) + where toRange previous source = Range (end previous) $ end previous + sourceLength source -- | Compute the byte 'Range' corresponding to a given 'Span' in a 'Source'. spanToRange :: Source -> Span -> Range @@ -85,7 +85,7 @@ rangeToSpan source (Range rangeStart rangeEnd) = Span startPos endPos -- | Return a 'Range' that covers the entire text. totalRange :: Source -> Range -totalRange = Range 0 . B.length . sourceText +totalRange = Range 0 . B.length . sourceBytes -- | Return a 'Span' that covers the entire text. totalSpan :: Source -> Span @@ -94,10 +94,10 @@ totalSpan source = Span (Pos 1 1) (Pos (length ranges) (succ (end lastRange - st Just lastRange = getLast (foldMap (Last . Just) ranges) sourceLength :: Source -> Int -sourceLength = B.length . sourceText +sourceLength = B.length . sourceBytes nullSource :: Source -> Bool -nullSource = B.null . sourceText +nullSource = B.null . sourceBytes instance Semigroup Source where Source a <> Source b = Source (a <> b) @@ -120,4 +120,4 @@ instance Listable ListableByteString where , [chr 0xa0..chr 0x24f] ] -- Non-ASCII. instance StringConv Source ByteString where - strConv _ = sourceText + strConv _ = sourceBytes diff --git a/src/Data/Syntax/Assignment.hs b/src/Data/Syntax/Assignment.hs index addc8448d..6b0831b9f 100644 --- a/src/Data/Syntax/Assignment.hs +++ b/src/Data/Syntax/Assignment.hs @@ -95,7 +95,7 @@ import Data.Ix (inRange) import Data.List.NonEmpty (nonEmpty) import Data.Range (offsetRange) import Data.Record -import qualified Data.Source as Source (Source(..), drop, slice, sourceText, actualLines) +import qualified Data.Source as Source (Source(..), drop, slice, sourceBytes, actualLines) import GHC.Stack import qualified Info import Prologue hiding (Alt, get, Location, state) @@ -188,7 +188,7 @@ printError source error@Error{..} withSGRCode [SetColor Foreground Vivid Red] . putStrErr . (showString "error") . showString ": " . showExpectation error . showChar '\n' . showString (toS context) . (if isSuffixOf "\n" context then identity else showChar '\n') . showString (replicate (succ (Info.posColumn errorPos + lineNumberDigits)) ' ') $ "" withSGRCode [SetColor Foreground Vivid Green] . putStrErr . (showChar '^') . showChar '\n' . showString (prettyCallStack callStack) $ "" - where context = maybe "\n" (Source.sourceText . sconcat) (nonEmpty [ Source.Source (toS (showLineNumber i)) <> Source.Source ": " <> l | (i, l) <- zip [1..] (Source.actualLines source), inRange (Info.posLine errorPos - 2, Info.posLine errorPos) i ]) + where context = maybe "\n" (Source.sourceBytes . sconcat) (nonEmpty [ Source.Source (toS (showLineNumber i)) <> Source.Source ": " <> l | (i, l) <- zip [1..] (Source.actualLines source), inRange (Info.posLine errorPos - 2, Info.posLine errorPos) i ]) showLineNumber n = let s = show n in replicate (lineNumberDigits - length s) ' ' <> s lineNumberDigits = succ (floor (logBase 10 (fromIntegral (Info.posLine errorPos) :: Double))) putStrErr = hPutStr stderr @@ -243,7 +243,7 @@ runAssignment toRecord = iterFreer run . fmap ((pure .) . (,)) (Location, node : _) -> yield (rtail (toRecord (F.project node))) state (Location, []) -> yield (Info.Range stateOffset stateOffset :. Info.Span statePos statePos :. Nil) state (Project projection, node : _) -> yield (projection (F.project node)) state - (Source, node : _) -> yield (Source.sourceText (Source.slice (offsetRange (Info.byteRange (toRecord (F.project node))) (negate stateOffset)) stateSource)) (advanceState (rtail . toRecord) state) + (Source, node : _) -> yield (Source.sourceBytes (Source.slice (offsetRange (Info.byteRange (toRecord (F.project node))) (negate stateOffset)) stateSource)) (advanceState (rtail . toRecord) state) (Children childAssignment, node : _) -> case assignAllFrom toRecord childAssignment state { stateNodes = toList (F.project node) } of Result _ (Just (a, state')) -> yield a (advanceState (rtail . toRecord) state' { stateNodes = stateNodes }) Result err Nothing -> Result err Nothing diff --git a/src/Renderer/Patch.hs b/src/Renderer/Patch.hs index 3de21171d..eadb7a0fa 100644 --- a/src/Renderer/Patch.hs +++ b/src/Renderer/Patch.hs @@ -90,7 +90,7 @@ showLines source prefix lines = fromMaybe "" . mconcat $ fmap prepend . showLine -- | Given a source, render a line to a string. showLine :: Functor f => HasField fields Range => Source -> Maybe (SplitDiff f (Record fields)) -> Maybe ByteString -showLine source line | Just line <- line = Just . sourceText . (`slice` source) $ getRange line +showLine source line | Just line <- line = Just . sourceBytes . (`slice` source) $ getRange line | otherwise = Nothing -- | Returns the header given two source blobs and a hunk.