{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE UndecidableInstances #-}
module Language.Ninja.Misc.Located
(
Located
, tokenize, tokenizeFile, tokenizeText
, locatedPos, locatedVal
, Spans, makeSpans, spansSet
, Span, makeSpan, spanPath, spanRange
, spanStart, spanEnd, spanStartPos, spanEndPos
, Position, makePosition
, positionFile, positionOffset, positionLine, positionCol
, comparePosition
, Offset, compareOffset, offsetLine, offsetColumn
, Line, Column
) where
import Control.Arrow (second, (&&&), (***))
import qualified Control.Lens as Lens
import Control.Monad.ST (ST)
import qualified Control.Monad.ST as ST
import Data.STRef (STRef)
import qualified Data.STRef as ST
import Data.Char (isSpace)
import qualified Data.Maybe
import Data.Semigroup (Semigroup ((<>)))
import Data.Text (Text)
import qualified Data.Text as Text
import Data.HashSet (HashSet)
import qualified Data.HashSet as HS
import Control.DeepSeq (NFData)
import Data.Hashable (Hashable)
import GHC.Generics (Generic)
import qualified Test.SmallCheck.Series as SC
import Data.Aeson ((.:), (.=))
import qualified Data.Aeson as Aeson
import qualified Data.Aeson.Types as Aeson
import Flow ((.>), (|>))
import qualified Language.Ninja.Misc.Path as Misc
import qualified Language.Ninja.Mock as Mock
data Located t
= MkLocated
{ _locatedPos :: {-# UNPACK #-} !Position
, _locatedVal :: !t
}
deriving (Eq, Show, Generic, Functor, Foldable, Traversable)
{-# INLINE makeLocated #-}
makeLocated :: Position -> t -> Located t
makeLocated = MkLocated
tokenize :: Maybe Misc.Path -> Text -> [Located Text]
tokenize mpath = removeWhitespace (mpath, 0, 0)
tokenizeFile :: (Mock.MonadReadFile m) => Misc.Path -> m [Located Text]
tokenizeFile path = tokenize (Just path) <$> Mock.readFile path
tokenizeText :: Text -> [Located Text]
tokenizeText = tokenize Nothing
{-# INLINE locatedPos #-}
locatedPos :: Lens.Lens' (Located t) Position
locatedPos = Lens.lens _locatedPos
$ \(MkLocated {..}) x -> MkLocated { _locatedPos = x, .. }
{-# INLINE locatedVal #-}
locatedVal :: Lens.Lens' (Located t) t
locatedVal = Lens.lens _locatedVal
$ \(MkLocated {..}) x -> MkLocated { _locatedVal = x, .. }
instance (Aeson.ToJSON t) => Aeson.ToJSON (Located t) where
toJSON (MkLocated {..})
= [ "pos" .= _locatedPos
, "val" .= _locatedVal
] |> Aeson.object
instance (Aeson.FromJSON t) => Aeson.FromJSON (Located t) where
parseJSON = (Aeson.withObject "Located" $ \o -> do
_locatedPos <- (o .: "pos") >>= pure
_locatedVal <- (o .: "val") >>= pure
pure (MkLocated {..}))
instance (Hashable t) => Hashable (Located t)
instance (NFData t) => NFData (Located t)
instance ( Monad m, SC.Serial m Text, SC.Serial m t
) => SC.Serial m (Located t)
instance ( Monad m, SC.CoSerial m Text, SC.CoSerial m t
) => SC.CoSerial m (Located t)
newtype Spans
= MkSpans (HashSet Span)
deriving ( Eq, Show, Semigroup, Monoid
, Generic, Aeson.ToJSON, Aeson.FromJSON
, Hashable, NFData )
{-# INLINE makeSpans #-}
makeSpans :: [Span] -> Spans
makeSpans = HS.fromList .> MkSpans
{-# INLINE spansSet #-}
spansSet :: Lens.Iso' Spans (HashSet Span)
spansSet = Lens.iso (\(MkSpans s) -> s) MkSpans
instance (Monad m, SC.Serial m (HashSet Span)) => SC.Serial m Spans
instance (Monad m, SC.CoSerial m (HashSet Span)) => SC.CoSerial m Spans
data Span
= MkSpan !(Maybe Misc.Path) !Offset !Offset
deriving (Eq, Show, Generic)
{-# INLINE makeSpan #-}
makeSpan :: Maybe Misc.Path
-> Offset
-> Offset
-> Span
makeSpan mpath start end = case compareOffset start end of
GT -> makeSpan mpath end start
_ -> MkSpan mpath start end
{-# INLINE spanPath #-}
spanPath :: Lens.Lens' Span (Maybe Misc.Path)
spanPath = let helper (MkSpan p s e) = (p, \x -> MkSpan x s e)
in Lens.lens (helper .> fst) (helper .> snd)
{-# INLINE spanRange #-}
spanRange :: Lens.Lens' Span (Offset, Offset)
spanRange = let helper (MkSpan p s e) = ((s, e), \(s', e') -> MkSpan p s' e')
in Lens.lens (helper .> fst) (helper .> snd)
{-# INLINE spanStart #-}
spanStart :: Lens.Lens' Span Offset
spanStart = spanRange . Lens._1
{-# INLINE spanEnd #-}
spanEnd :: Lens.Lens' Span Offset
spanEnd = spanRange . Lens._2
{-# INLINE spanStartPos #-}
spanStartPos :: Lens.Getter Span Position
spanStartPos = Lens.to (\(MkSpan p s _) -> makePosition p s)
{-# INLINE spanEndPos #-}
spanEndPos :: Lens.Getter Span Position
spanEndPos = Lens.to (\(MkSpan p _ e) -> makePosition p e)
instance Aeson.ToJSON Span where
toJSON (MkSpan file start end)
= [ "file" .= maybe Aeson.Null Aeson.toJSON file
, "start" .= offsetJ start
, "end" .= offsetJ end
] |> Aeson.object
where
offsetJ :: (Line, Column) -> Aeson.Value
offsetJ (line, col) = Aeson.object ["line" .= line, "col" .= col]
instance Aeson.FromJSON Span where
parseJSON = (Aeson.withObject "Span" $ \o -> do
file <- (o .: "file") >>= pure
start <- (o .: "start") >>= offsetP
end <- (o .: "end") >>= offsetP
pure (MkSpan file start end))
where
offsetP :: Aeson.Value -> Aeson.Parser Offset
offsetP = (Aeson.withObject "Offset" $ \o -> do
line <- (o .: "line") >>= pure
col <- (o .: "col") >>= pure
pure (line, col))
instance Hashable Span
instance NFData Span
instance (Monad m, SC.Serial m Text) => SC.Serial m Span
instance (Monad m, SC.CoSerial m Text) => SC.CoSerial m Span
data Position
= MkPosition
{ _positionFile :: !(Maybe Misc.Path)
, _positionLine :: {-# UNPACK #-} !Line
, _positionCol :: {-# UNPACK #-} !Column
}
deriving (Eq, Show, Generic)
{-# INLINE makePosition #-}
makePosition :: Maybe Misc.Path -> Offset -> Position
makePosition file (line, column) = MkPosition file line column
{-# INLINE positionFile #-}
positionFile :: Lens.Lens' Position (Maybe Misc.Path)
positionFile = Lens.lens _positionFile
$ \(MkPosition {..}) x -> MkPosition { _positionFile = x, .. }
{-# INLINE positionOffset #-}
positionOffset :: Lens.Lens' Position Offset
positionOffset
= Lens.lens (_positionLine &&& _positionCol)
$ \(MkPosition {..}) (line, col) ->
MkPosition { _positionLine = line, _positionCol = col, .. }
{-# INLINE positionLine #-}
positionLine :: Lens.Lens' Position Line
positionLine = positionOffset . Lens._1
{-# INLINE positionCol #-}
positionCol :: Lens.Lens' Position Column
positionCol = positionOffset . Lens._2
comparePosition :: Position -> Position -> Maybe Ordering
comparePosition = go
where
go (MkPosition fileX lineX colX) (MkPosition fileY lineY colY)
= compareTriple (fileX, (lineX, colX)) (fileY, (lineY, colY))
compareTriple :: (Maybe Misc.Path, Offset) -> (Maybe Misc.Path, Offset)
-> Maybe Ordering
compareTriple (mfileX, offX) (mfileY, offY)
| (mfileX == mfileY) = Just (compareOffset offX offY)
| otherwise = Nothing
instance Aeson.ToJSON Position where
toJSON (MkPosition {..})
= [ "file" .= _positionFile
, "line" .= _positionLine
, "col" .= _positionCol
] |> Aeson.object
instance Aeson.FromJSON Position where
parseJSON = (Aeson.withObject "Position" $ \o -> do
_positionFile <- (o .: "file") >>= pure
_positionLine <- (o .: "line") >>= pure
_positionCol <- (o .: "col") >>= pure
pure (MkPosition {..}))
instance Hashable Position
instance NFData Position
instance (Monad m, SC.Serial m Text) => SC.Serial m Position
instance (Monad m, SC.CoSerial m Text) => SC.CoSerial m Position
type Offset = (Line, Column)
compareOffset :: Offset -> Offset -> Ordering
compareOffset (lineX, colX) (lineY, colY)
| (lineX < lineY) = LT
| (lineX > lineY) = GT
| otherwise = compare colX colY
{-# INLINE offsetLine #-}
offsetLine :: Lens.Lens' Offset Line
offsetLine = Lens._1
{-# INLINE offsetColumn #-}
offsetColumn :: Lens.Lens' Offset Column
offsetColumn = Lens._2
type Line = Int
type Column = Int
data Chunk
= ChunkText !Text
| ChunkSpace {-# UNPACK #-} !Int
| ChunkLine {-# UNPACK #-} !Int
deriving (Eq, Show)
newtype Chunks
= MkChunks { fromChunks :: [Chunk] }
deriving (Eq, Show)
{-# INLINE chunksNil #-}
chunksNil :: Chunks
chunksNil = MkChunks []
chunksCons :: Chunk -> Chunks -> Chunks
chunksCons = \chunk (MkChunks list) -> MkChunks (go chunk list)
where
{-# INLINE go #-}
go (ChunkSpace m) (ChunkSpace n : rest) = ChunkSpace (m + n) : rest
go (ChunkLine m) (ChunkLine n : rest) = ChunkLine (m + n) : rest
go (ChunkText a) (ChunkText b : rest) = ChunkText (a <> b) : rest
go other list = other : list
{-# INLINE chunksAddChar #-}
chunksAddChar :: Char -> Chunks -> Chunks
chunksAddChar '\n' = chunksCons (ChunkLine 1)
chunksAddChar '\r' = id
chunksAddChar c | isSpace c = chunksCons (ChunkSpace 1)
chunksAddChar c = chunksCons (ChunkText (Text.singleton c))
removeWhitespace :: (Maybe Misc.Path, Line, Column) -> Text -> [Located Text]
removeWhitespace (file, initLine, initCol) =
go .> Data.Maybe.catMaybes .> map makeLoc
where
go :: Text -> [Maybe (Line, Column, Text)]
go text = ST.runST $ do
ref <- ST.newSTRef (initLine, initCol)
Text.foldr chunksAddChar chunksNil text
|> fromChunks
|> mapM (applyChunk ref)
applyChunk :: STRef s (Line, Column)
-> Chunk -> ST s (Maybe (Line, Column, Text))
applyChunk ref = \case
ChunkLine n -> do ST.modifySTRef' ref ((+ n) *** const 0)
pure Nothing
ChunkSpace n -> do ST.modifySTRef' ref (second (+ n))
pure Nothing
ChunkText t -> do (line, column) <- ST.readSTRef ref
ST.modifySTRef' ref (second (+ Text.length t))
pure (Just (line, column, t))
{-# INLINE makeLoc #-}
makeLoc :: (Line, Column, Text) -> Located Text
makeLoc (line, col, text) = makeLocated (MkPosition file line col) text