1
1
mirror of https://github.com/github/semantic.git synced 2024-12-23 23:11:50 +03:00
semantic/src/Source.hs

93 lines
3.3 KiB
Haskell
Raw Normal View History

{-# LANGUAGE GeneralizedNewtypeDeriving #-}
2015-12-24 06:38:02 +03:00
module Source where
import Prologue hiding (uncons)
import Data.Text (unpack, pack)
import Data.String
import qualified Data.Vector as Vector
2016-03-08 03:20:28 +03:00
import Numeric
import Range
2016-03-08 03:20:28 +03:00
data SourceKind = PlainBlob Word32 | ExecutableBlob Word32 | SymlinkBlob Word32
2016-03-08 02:50:32 +03:00
deriving (Show, Eq)
2016-03-04 00:29:03 +03:00
2016-03-04 01:09:46 +03:00
modeToDigits :: SourceKind -> String
2016-03-08 03:20:28 +03:00
modeToDigits (PlainBlob mode) = showOct mode ""
modeToDigits (ExecutableBlob mode) = showOct mode ""
modeToDigits (SymlinkBlob mode) = showOct mode ""
2016-03-04 01:09:46 +03:00
data SourceBlob = SourceBlob { source :: Source Char, oid :: String, path :: FilePath, blobKind :: Maybe SourceKind }
2016-03-02 01:00:44 +03:00
deriving (Show, Eq)
2016-01-27 00:25:40 +03:00
2016-03-09 00:04:44 +03:00
-- | The default plain blob mode
defaultPlainBlob :: SourceKind
defaultPlainBlob = PlainBlob 0o100644
2016-01-13 23:50:52 +03:00
-- | The contents of a source file, backed by a vector for efficient slicing.
newtype Source a = Source { getVector :: Vector.Vector a }
deriving (Eq, Show, Foldable, Functor, Traversable)
-- | Map blobs with Nothing blobKind to empty blobs.
idOrEmptySourceBlob :: SourceBlob -> SourceBlob
2016-06-02 00:41:28 +03:00
idOrEmptySourceBlob blob = if isNothing (blobKind blob)
then blob { oid = nullOid, blobKind = Nothing }
else blob
nullOid :: String
nullOid = "0000000000000000000000000000000000000000"
2016-01-13 23:50:52 +03:00
-- | Return a Source from a list of items.
2015-12-24 07:37:51 +03:00
fromList :: [a] -> Source a
fromList = Source . Vector.fromList
2016-01-13 23:50:52 +03:00
-- | Return a Source of Chars from a Text.
fromText :: Text -> Source Char
fromText = Source . Vector.fromList . unpack
2015-12-30 01:34:52 +03:00
2016-01-13 23:50:52 +03:00
-- | Return a Source that contains a slice of the given Source.
2015-12-24 07:25:00 +03:00
slice :: Range -> Source a -> Source a
2016-01-12 19:56:36 +03:00
slice range = Source . Vector.slice (start range) (rangeLength range) . getVector
2016-01-13 23:50:52 +03:00
-- | Return a String with the contents of the Source.
toString :: Source Char -> String
2015-12-24 07:26:37 +03:00
toString = toList
-- | Return a text with the contents of the Source.
toText :: Source Char -> Text
toText = pack . toList
2016-01-13 23:50:52 +03:00
-- | Return the item at the given index.
at :: Source a -> Int -> a
2015-12-24 07:29:27 +03:00
at = (Vector.!) . getVector
2016-01-13 23:50:52 +03:00
-- | Remove the first item and return it with the rest of the source.
2015-12-24 07:05:01 +03:00
uncons :: Source a -> Maybe (a, Source a)
uncons (Source vector) = if null vector then Nothing else Just (Vector.head vector, Source $ Vector.tail vector)
2015-12-24 07:16:09 +03:00
2016-01-13 23:50:52 +03:00
-- | Split the source into the longest prefix of elements that do not satisfy the predicate and the rest without copying.
2015-12-24 07:16:09 +03:00
break :: (a -> Bool) -> Source a -> (Source a, Source a)
2015-12-24 07:23:16 +03:00
break predicate (Source vector) = let (start, remainder) = Vector.break predicate vector in (Source start, Source remainder)
2015-12-24 07:41:08 +03:00
2016-01-13 23:50:52 +03:00
-- | Concatenate two sources.
2015-12-24 07:41:08 +03:00
(++) :: Source a -> Source a -> Source a
(++) (Source a) = Source . (a Vector.++) . getVector
2016-01-14 00:20:29 +03:00
-- | Split the contents of the source after newlines.
actualLines :: Source Char -> [Source Char]
actualLines source | null source = [ source ]
actualLines source = case Source.break (== '\n') source of
(l, lines') -> case uncons lines' of
Nothing -> [ l ]
Just (_, lines') -> (l Source.++ fromList "\n") : actualLines lines'
-- | Compute the line ranges within a given range of a string.
actualLineRanges :: Range -> Source Char -> [Range]
actualLineRanges range = drop 1 . scanl toRange (Range (start range) (start range)) . actualLines . slice range
where toRange previous string = Range (end previous) $ end previous + length string
2016-05-21 05:38:55 +03:00
instance Monoid (Source a) where
mempty = fromList []
mappend = (Source.++)