1
1
mirror of https://github.com/github/semantic.git synced 2024-12-25 16:02:43 +03:00

Move SourceBlob into Data.Blob.

This commit is contained in:
Rob Rix 2017-06-24 10:09:50 -04:00
parent 84c7029dd8
commit fc51c92425
12 changed files with 62 additions and 51 deletions

View File

@ -10,7 +10,8 @@ import Control.Exception (catch, IOException)
import Data.Aeson
import Data.These
import Data.Functor.Both
import Data.Source hiding (path)
import Data.Blob hiding (path)
import Data.Source
import Data.String
import Language
import Prologue hiding (readFile)

View File

@ -1 +1,50 @@
module Data.Blob where
import Data.Source as Source
import Language
import Numeric
import Prologue
-- | The source, oid, path, and Maybe SourceKind of a blob.
data SourceBlob = SourceBlob
{ source :: Source -- ^ The UTF-8 encoded source text of the blob.
, oid :: ByteString -- ^ The Git object ID (SHA-1) of the blob.
, path :: FilePath -- ^ The file path to the blob.
, blobKind :: Maybe SourceKind -- ^ The kind of blob, Nothing denotes a blob that doesn't exist (e.g. on one side of a diff for adding a new file or deleting a file).
, blobLanguage :: Maybe Language -- ^ The language of this blob. Nothing denotes a langauge we don't support yet.
}
deriving (Show, Eq)
-- | The kind of a blob, along with it's file mode.
data SourceKind = PlainBlob Word32 | ExecutableBlob Word32 | SymlinkBlob Word32
deriving (Show, Eq)
modeToDigits :: SourceKind -> ByteString
modeToDigits (PlainBlob mode) = toS $ showOct mode ""
modeToDigits (ExecutableBlob mode) = toS $ showOct mode ""
modeToDigits (SymlinkBlob mode) = toS $ showOct mode ""
-- | The default plain blob mode
defaultPlainBlob :: SourceKind
defaultPlainBlob = PlainBlob 0o100644
emptySourceBlob :: FilePath -> SourceBlob
emptySourceBlob filepath = SourceBlob mempty nullOid filepath Nothing Nothing
nullBlob :: SourceBlob -> Bool
nullBlob SourceBlob{..} = oid == nullOid || Source.null source
blobExists :: SourceBlob -> Bool
blobExists SourceBlob{..} = isJust blobKind
sourceBlob :: FilePath -> Maybe Language -> Source -> SourceBlob
sourceBlob filepath language source = SourceBlob source nullOid filepath (Just defaultPlainBlob) language
-- | Map blobs with Nothing blobKind to empty blobs.
idOrEmptySourceBlob :: SourceBlob -> SourceBlob
idOrEmptySourceBlob blob = if isNothing (blobKind blob)
then blob { oid = nullOid, blobKind = Nothing }
else blob
nullOid :: ByteString
nullOid = "0000000000000000000000000000000000000000"

View File

@ -8,58 +8,13 @@ import Data.Range
import Data.Span
import Data.String (IsString(..))
import qualified Data.Text as T
import Language
import Numeric
import Prologue
import System.IO (FilePath)
import Test.LeanCheck
-- | The source, oid, path, and Maybe SourceKind of a blob.
data SourceBlob = SourceBlob
{ source :: Source -- ^ The UTF-8 encoded source text of the blob.
, oid :: ByteString -- ^ The Git object ID (SHA-1) of the blob.
, path :: FilePath -- ^ The file path to the blob.
, blobKind :: Maybe SourceKind -- ^ The kind of blob, Nothing denotes a blob that doesn't exist (e.g. on one side of a diff for adding a new file or deleting a file).
, blobLanguage :: Maybe Language -- ^ The language of this blob. Nothing denotes a langauge we don't support yet.
} deriving (Show, Eq)
-- | The contents of a source file, represented as a ByteString.
newtype Source = Source { sourceText :: B.ByteString }
deriving (Eq, IsString, Show)
-- | The kind of a blob, along with it's file mode.
data SourceKind = PlainBlob Word32 | ExecutableBlob Word32 | SymlinkBlob Word32
deriving (Show, Eq)
modeToDigits :: SourceKind -> ByteString
modeToDigits (PlainBlob mode) = toS $ showOct mode ""
modeToDigits (ExecutableBlob mode) = toS $ showOct mode ""
modeToDigits (SymlinkBlob mode) = toS $ showOct mode ""
-- | The default plain blob mode
defaultPlainBlob :: SourceKind
defaultPlainBlob = PlainBlob 0o100644
emptySourceBlob :: FilePath -> SourceBlob
emptySourceBlob filepath = SourceBlob Data.Source.empty Data.Source.nullOid filepath Nothing Nothing
nullBlob :: SourceBlob -> Bool
nullBlob SourceBlob{..} = oid == nullOid || Data.Source.null source
blobExists :: SourceBlob -> Bool
blobExists SourceBlob{..} = isJust blobKind
sourceBlob :: FilePath -> Maybe Language -> Source -> SourceBlob
sourceBlob filepath language source = SourceBlob source Data.Source.nullOid filepath (Just defaultPlainBlob) language
-- | Map blobs with Nothing blobKind to empty blobs.
idOrEmptySourceBlob :: SourceBlob -> SourceBlob
idOrEmptySourceBlob blob = if isNothing (blobKind blob)
then blob { oid = nullOid, blobKind = Nothing }
else blob
nullOid :: ByteString
nullOid = "0000000000000000000000000000000000000000"
empty :: Source
empty = Source B.empty

View File

@ -9,10 +9,10 @@ module Renderer.JSON
import Data.Aeson (ToJSON, toJSON, encode, object, (.=))
import Data.Aeson as A hiding (json)
import Data.Bifunctor.Join
import Data.Blob
import Data.Functor.Both (Both)
import qualified Data.Map as Map
import Data.Record
import Data.Source
import Data.Union
import Info
import Language

View File

@ -9,6 +9,7 @@ module Renderer.Patch
import Alignment
import Data.Bifunctor.Join
import Data.Blob
import qualified Data.ByteString.Char8 as ByteString
import Data.Functor.Both as Both
import Data.List (span, unzip)

View File

@ -19,6 +19,7 @@ module Renderer.TOC
import Data.Aeson
import Data.Align (crosswalk)
import Data.Blob
import Data.Functor.Both hiding (fst, snd)
import qualified Data.Functor.Both as Both
import Data.Functor.Listable

View File

@ -9,6 +9,7 @@ module Semantic
import Algorithm hiding (diff)
import Data.Align.Generic (GAlign)
import Data.Blob
import Data.Functor.Both as Both
import Data.Functor.Classes (Eq1, Show1)
import Data.Proxy

View File

@ -1,6 +1,7 @@
module CommandSpec where
import Command
import Data.Blob
import Data.Functor.Both as Both
import Data.Maybe
import Data.Source

View File

@ -1,10 +1,10 @@
module PatchOutputSpec where
import Prologue
import Data.Blob
import Data.Functor.Both
import Data.Range
import Data.Record
import Data.Source as Source
import Renderer.Patch
import Syntax
import Test.Hspec (Spec, describe, it, parallel)
@ -14,4 +14,4 @@ spec :: Spec
spec = parallel $ do
describe "hunks" $ do
it "empty diffs have empty hunks" $
hunks (wrap $ pure (Range 0 0 :. Nil) :< Leaf ("" :: Text)) (both (SourceBlob Source.empty "abcde" "path2.txt" (Just defaultPlainBlob) Nothing) (SourceBlob Source.empty "xyz" "path2.txt" (Just defaultPlainBlob) Nothing)) `shouldBe` [Hunk {offset = pure 0, changes = [], trailingContext = []}]
hunks (wrap $ pure (Range 0 0 :. Nil) :< Leaf ("" :: Text)) (both (SourceBlob mempty "abcde" "path2.txt" (Just defaultPlainBlob) Nothing) (SourceBlob mempty "xyz" "path2.txt" (Just defaultPlainBlob) Nothing)) `shouldBe` [Hunk {offset = pure 0, changes = [], trailingContext = []}]

View File

@ -1,7 +1,7 @@
module SemanticSpec where
import Data.Blob
import Data.Functor.Both as Both
import Data.Source
import Language
import Patch
import Prologue
@ -37,4 +37,4 @@ spec = parallel $ do
(() <$) <$> result `shouldBe` pure (Delete ())
where
methodsBlob = SourceBlob (Source "def foo\nend\n") "ff7bbbe9495f61d9e1e58c597502d152bab1761e" "methods.rb" (Just defaultPlainBlob) (Just Ruby)
methodsBlob = SourceBlob "def foo\nend\n" "ff7bbbe9495f61d9e1e58c597502d152bab1761e" "methods.rb" (Just defaultPlainBlob) (Just Ruby)

View File

@ -7,6 +7,7 @@ module SpecHelpers
, unListableDiff
) where
import Data.Blob
import qualified Data.ByteString as B
import Data.Functor.Both
import Data.Functor.Listable

View File

@ -4,6 +4,7 @@ module TOCSpec where
import Data.Aeson
import Category as C
import Data.Blob
import Data.Functor.Both
import Data.Functor.Listable
import Data.Record