mirror of
https://github.com/github/semantic.git
synced 2024-12-11 08:45:48 +03:00
Merge branch 'master' into python
This commit is contained in:
commit
4bf0ad07dc
@ -3,14 +3,14 @@
|
||||
module Arguments where
|
||||
|
||||
import Data.Maybe
|
||||
import Language
|
||||
import Prelude
|
||||
import Prologue
|
||||
import Renderer
|
||||
import Renderer.SExpression
|
||||
import Info
|
||||
|
||||
|
||||
data DiffMode = DiffCommits String String [FilePath] | DiffPaths FilePath FilePath
|
||||
data DiffMode = DiffCommits String String [(FilePath, Maybe Language)] | DiffPaths (FilePath, Maybe Language) (FilePath, Maybe Language)
|
||||
deriving Show
|
||||
|
||||
data DiffArguments where
|
||||
@ -23,23 +23,25 @@ data DiffArguments where
|
||||
|
||||
deriving instance Show DiffArguments
|
||||
|
||||
patchDiff :: DiffMode -> FilePath -> [FilePath] -> DiffArguments
|
||||
type DiffArguments' = DiffMode -> FilePath -> [FilePath] -> DiffArguments
|
||||
|
||||
patchDiff :: DiffArguments'
|
||||
patchDiff = DiffArguments PatchRenderer
|
||||
|
||||
jsonDiff :: DiffMode -> FilePath -> [FilePath] -> DiffArguments
|
||||
jsonDiff :: DiffArguments'
|
||||
jsonDiff = DiffArguments JSONDiffRenderer
|
||||
|
||||
summaryDiff :: DiffMode -> FilePath -> [FilePath] -> DiffArguments
|
||||
summaryDiff :: DiffArguments'
|
||||
summaryDiff = DiffArguments SummaryRenderer
|
||||
|
||||
sExpressionDiff :: DiffMode -> FilePath -> [FilePath] -> DiffArguments
|
||||
sExpressionDiff :: DiffArguments'
|
||||
sExpressionDiff = DiffArguments (SExpressionDiffRenderer TreeOnly)
|
||||
|
||||
tocDiff :: DiffMode -> FilePath -> [FilePath] -> DiffArguments
|
||||
tocDiff :: DiffArguments'
|
||||
tocDiff = DiffArguments ToCRenderer
|
||||
|
||||
|
||||
data ParseMode = ParseCommit String [FilePath] | ParsePaths [FilePath]
|
||||
data ParseMode = ParseCommit String [(FilePath, Maybe Language)] | ParsePaths [(FilePath, Maybe Language)]
|
||||
deriving Show
|
||||
|
||||
data ParseArguments where
|
||||
@ -52,10 +54,12 @@ data ParseArguments where
|
||||
|
||||
deriving instance Show ParseArguments
|
||||
|
||||
sExpressionParseTree :: ParseMode -> FilePath -> [FilePath] -> ParseArguments
|
||||
type ParseArguments' = ParseMode -> FilePath -> [FilePath] -> ParseArguments
|
||||
|
||||
sExpressionParseTree :: ParseArguments'
|
||||
sExpressionParseTree = ParseArguments (SExpressionParseTreeRenderer TreeOnly)
|
||||
|
||||
jsonParseTree :: ParseMode -> FilePath -> [FilePath] -> ParseArguments
|
||||
jsonParseTree :: ParseArguments'
|
||||
jsonParseTree = ParseArguments JSONParseTreeRenderer
|
||||
|
||||
data ProgramMode = Parse ParseArguments | Diff DiffArguments
|
||||
|
@ -17,6 +17,7 @@ import Data.Functor.Both
|
||||
import Data.Functor.Classes
|
||||
import Data.String
|
||||
import Prologue hiding (readFile)
|
||||
import Language
|
||||
import Source
|
||||
import Text.Show
|
||||
|
||||
@ -28,13 +29,13 @@ type Command = Freer CommandF
|
||||
-- Constructors
|
||||
|
||||
-- | Read a file into a SourceBlob.
|
||||
readFile :: FilePath -> Command SourceBlob
|
||||
readFile path = ReadFile path `Then` return
|
||||
readFile :: FilePath -> Maybe Language -> Command SourceBlob
|
||||
readFile path lang = ReadFile path lang `Then` return
|
||||
|
||||
-- | Read a list of files at the given commit SHA.
|
||||
readFilesAtSHA :: FilePath -- ^ GIT_DIR
|
||||
-> [FilePath] -- ^ GIT_ALTERNATE_OBJECT_DIRECTORIES
|
||||
-> [FilePath] -- ^ Specific paths. If empty, return changed paths.
|
||||
-> [(FilePath, Maybe Language)] -- ^ Specific paths. If empty, return changed paths.
|
||||
-> String -- ^ The commit SHA.
|
||||
-> Command [SourceBlob] -- ^ A command producing a list of pairs of blobs for the specified files (or all files if none were specified).
|
||||
readFilesAtSHA gitDir alternates paths sha = ReadFilesAtSHA gitDir alternates paths sha `Then` return
|
||||
@ -42,7 +43,7 @@ readFilesAtSHA gitDir alternates paths sha = ReadFilesAtSHA gitDir alternates pa
|
||||
-- | Read a list of files at the states corresponding to the given shas.
|
||||
readFilesAtSHAs :: FilePath -- ^ GIT_DIR
|
||||
-> [FilePath] -- ^ GIT_ALTERNATE_OBJECT_DIRECTORIES
|
||||
-> [FilePath] -- ^ Specific paths. If empty, return changed paths.
|
||||
-> [(FilePath, Maybe Language)] -- ^ Specific paths. If empty, return changed paths.
|
||||
-> Both String -- ^ The commit shas for the before & after states.
|
||||
-> Command [Both SourceBlob] -- ^ A command producing a list of pairs of blobs for the specified files (or all files if none were specified).
|
||||
readFilesAtSHAs gitDir alternates paths shas = ReadFilesAtSHAs gitDir alternates paths shas `Then` return
|
||||
@ -53,7 +54,7 @@ readFilesAtSHAs gitDir alternates paths shas = ReadFilesAtSHAs gitDir alternates
|
||||
-- | Run the passed command and return its results in IO.
|
||||
runCommand :: Command a -> IO a
|
||||
runCommand = iterFreerA $ \ command yield -> case command of
|
||||
ReadFile path -> Files.readFile path >>= yield
|
||||
ReadFile path lang -> Files.readFile path lang >>= yield
|
||||
ReadFilesAtSHA gitDir alternates paths sha -> Git.readFilesAtSHA gitDir alternates paths sha >>= yield
|
||||
ReadFilesAtSHAs gitDir alternates paths shas -> Git.readFilesAtSHAs gitDir alternates paths shas >>= yield
|
||||
LiftIO io -> io >>= yield
|
||||
@ -62,9 +63,9 @@ runCommand = iterFreerA $ \ command yield -> case command of
|
||||
-- Implementation details
|
||||
|
||||
data CommandF f where
|
||||
ReadFile :: FilePath -> CommandF SourceBlob
|
||||
ReadFilesAtSHA :: FilePath -> [FilePath] -> [FilePath] -> String -> CommandF [SourceBlob]
|
||||
ReadFilesAtSHAs :: FilePath -> [FilePath] -> [FilePath] -> Both String -> CommandF [Both SourceBlob]
|
||||
ReadFile :: FilePath -> Maybe Language -> CommandF SourceBlob
|
||||
ReadFilesAtSHA :: FilePath -> [FilePath] -> [(FilePath, Maybe Language)] -> String -> CommandF [SourceBlob]
|
||||
ReadFilesAtSHAs :: FilePath -> [FilePath] -> [(FilePath, Maybe Language)] -> Both String -> CommandF [Both SourceBlob]
|
||||
LiftIO :: IO a -> CommandF a
|
||||
|
||||
instance MonadIO Command where
|
||||
@ -72,7 +73,7 @@ instance MonadIO Command where
|
||||
|
||||
instance Show1 CommandF where
|
||||
liftShowsPrec _ _ d command = case command of
|
||||
ReadFile path -> showsUnaryWith showsPrec "ReadFile" d path
|
||||
ReadFile path lang -> showsBinaryWith showsPrec showsPrec "ReadFile" d path lang
|
||||
ReadFilesAtSHA gitDir alternates paths sha -> showsQuaternaryWith showsPrec showsPrec showsPrec showsPrec "ReadFilesAtSHA" d gitDir alternates paths sha
|
||||
ReadFilesAtSHAs gitDir alternates paths shas -> showsQuaternaryWith showsPrec showsPrec showsPrec showsPrec "ReadFilesAtSHAs" d gitDir alternates paths shas
|
||||
LiftIO _ -> showsUnaryWith (const showChar) "LiftIO" d '_'
|
||||
|
@ -1,21 +1,24 @@
|
||||
module Command.Files
|
||||
( readFile
|
||||
, transcode
|
||||
, languageForFilePath
|
||||
) where
|
||||
|
||||
import Prologue hiding (readFile)
|
||||
import Language
|
||||
import Source
|
||||
import qualified Data.ByteString as B
|
||||
import System.FilePath
|
||||
import Control.Exception (catch, IOException)
|
||||
import qualified Data.Text.ICU.Convert as Convert
|
||||
import qualified Data.Text.ICU.Detect as Detect
|
||||
|
||||
-- | Read a file to a SourceBlob, transcoding to UTF-8 along the way.
|
||||
readFile :: FilePath -> IO SourceBlob
|
||||
readFile path = do
|
||||
readFile :: FilePath -> Maybe Language -> IO SourceBlob
|
||||
readFile path language = do
|
||||
raw <- (Just <$> B.readFile path) `catch` (const (pure Nothing) :: IOException -> IO (Maybe ByteString))
|
||||
source <- traverse transcode raw
|
||||
pure $ fromMaybe (emptySourceBlob path) (flip sourceBlob path <$> source)
|
||||
pure $ fromMaybe (emptySourceBlob path) (sourceBlob path language <$> source)
|
||||
|
||||
-- | Transcode a ByteString to a unicode Source.
|
||||
transcode :: B.ByteString -> IO Source
|
||||
@ -23,3 +26,7 @@ transcode text = fromText <$> do
|
||||
match <- Detect.detectCharset text
|
||||
converter <- Convert.open match Nothing
|
||||
pure $ Convert.toUnicode converter text
|
||||
|
||||
-- | Return a language based on a FilePath's extension, or Nothing if extension is not found or not supported.
|
||||
languageForFilePath :: FilePath -> Maybe Language
|
||||
languageForFilePath = languageForType . toS . takeExtension
|
||||
|
@ -16,30 +16,31 @@ import Git.Types
|
||||
import qualified Git
|
||||
import GitmonClient
|
||||
import Command.Files
|
||||
import Language
|
||||
import Source
|
||||
|
||||
-- | Read files at the specified commit SHA as blobs from a Git repo.
|
||||
readFilesAtSHA :: FilePath -> [FilePath] -> [FilePath] -> String -> IO [SourceBlob]
|
||||
readFilesAtSHA :: FilePath -> [FilePath] -> [(FilePath, Maybe Language)] -> String -> IO [SourceBlob]
|
||||
readFilesAtSHA gitDir alternates paths sha = runGit gitDir alternates $ do
|
||||
tree <- treeForSha sha
|
||||
traverse (`blobForPathInTree` tree) paths
|
||||
traverse (uncurry (blobForPathInTree tree)) paths
|
||||
|
||||
-- | Read files at the specified commit SHA pair as blobs from a Git repo.
|
||||
readFilesAtSHAs :: FilePath -> [FilePath] -> [FilePath] -> Both String -> IO [Both SourceBlob]
|
||||
readFilesAtSHAs :: FilePath -> [FilePath] -> [(FilePath, Maybe Language)] -> Both String -> IO [Both SourceBlob]
|
||||
readFilesAtSHAs gitDir alternates paths shas = do
|
||||
paths <- case paths of
|
||||
[] -> runGit' $ do
|
||||
trees <- for shas treeForSha
|
||||
paths <- for trees (reportGitmon "ls-tree" . treeBlobEntries)
|
||||
pure . nub $! (\ (p, _, _) -> toS p) <$> runBothWith (\\) paths <> runBothWith (flip (\\)) paths
|
||||
pure . nub $! (\ (p, _, _) -> (toS p, languageForFilePath (toS p))) <$> runBothWith (\\) paths <> runBothWith (flip (\\)) paths
|
||||
_ -> pure paths
|
||||
|
||||
Async.mapConcurrently (runGit' . blobsForPath) paths
|
||||
where
|
||||
runGit' = runGit gitDir alternates
|
||||
blobsForPath path = do
|
||||
blobsForPath (path, lang) = do
|
||||
trees <- traverse treeForSha shas
|
||||
traverse (blobForPathInTree path) trees
|
||||
traverse (\t -> blobForPathInTree t path lang) trees
|
||||
|
||||
runGit :: FilePath -> [FilePath] -> ReaderT LgRepo IO a -> IO a
|
||||
runGit gitDir alternates action = withRepository lgFactory gitDir $ do
|
||||
@ -53,8 +54,8 @@ treeForSha sha = do
|
||||
commit <- reportGitmon "cat-file" $ lookupCommit obj
|
||||
reportGitmon "cat-file" $ lookupTree (commitTree commit)
|
||||
|
||||
blobForPathInTree :: FilePath -> Git.Tree LgRepo -> ReaderT LgRepo IO SourceBlob
|
||||
blobForPathInTree path tree = do
|
||||
blobForPathInTree :: Git.Tree LgRepo -> FilePath -> Maybe Language -> ReaderT LgRepo IO SourceBlob
|
||||
blobForPathInTree tree path language = do
|
||||
entry <- reportGitmon "ls-tree" $ treeEntry tree (toS path)
|
||||
case entry of
|
||||
Just (BlobEntry entryOid entryKind) -> do
|
||||
@ -62,7 +63,7 @@ blobForPathInTree path tree = do
|
||||
contents <- blobToByteString blob
|
||||
transcoded <- liftIO $ transcode contents
|
||||
let oid = renderObjOid $ blobOid blob
|
||||
pure (SourceBlob transcoded (toS oid) path (Just (toSourceKind entryKind)))
|
||||
pure (SourceBlob transcoded (toS oid) path (Just (toSourceKind entryKind)) language)
|
||||
_ -> pure (emptySourceBlob path)
|
||||
where
|
||||
toSourceKind :: Git.BlobKind -> SourceKind
|
||||
|
@ -16,7 +16,7 @@ data Language =
|
||||
| Markdown
|
||||
| Ruby
|
||||
| TypeScript
|
||||
deriving (Show)
|
||||
deriving (Show, Eq, Read)
|
||||
|
||||
-- | Returns a Language based on the file extension (including the ".").
|
||||
languageForType :: String -> Maybe Language
|
||||
|
@ -32,10 +32,6 @@ import Text.Parser.TreeSitter.Ruby
|
||||
import Text.Parser.TreeSitter.TypeScript
|
||||
import TreeSitter
|
||||
|
||||
-- TODO: Shouldn't need to depend on System.FilePath in here, but this is
|
||||
-- currently the way we do language detection.
|
||||
import System.FilePath
|
||||
|
||||
-- This is the primary interface to the Semantic library which provides two
|
||||
-- major classes of functionality: semantic parsing and diffing of source code
|
||||
-- blobs.
|
||||
@ -85,7 +81,7 @@ parseBlobs renderer blobs = do
|
||||
|
||||
-- | Parse a SourceBlob.
|
||||
parseBlob :: SourceBlob -> IO (Term (Syntax Text) (Record DefaultFields))
|
||||
parseBlob blob@SourceBlob{..} = parserForFilePath path blob
|
||||
parseBlob blob@SourceBlob{..} = parserForLanguage blobLanguage blob
|
||||
|
||||
-- | Return a parser for a given langauge or the lineByLineParser parser.
|
||||
parserForLanguage :: Maybe Language -> Parser (Syntax Text) (Record DefaultFields)
|
||||
@ -106,11 +102,6 @@ renderConcurrently f diffs = do
|
||||
outputs <- Async.mapConcurrently (pure . uncurry f) diffs
|
||||
pure $ mconcat (outputs `using` parTraversable rseq)
|
||||
|
||||
-- | Return a parser based on the FilePath's extension (including the ".").
|
||||
-- | TODO: Remove this.
|
||||
parserForFilePath :: FilePath -> Parser (Syntax Text) (Record DefaultFields)
|
||||
parserForFilePath = parserForLanguage . languageForType . toS . takeExtension
|
||||
|
||||
-- | A fallback parser that treats a file simply as rows of strings.
|
||||
lineByLineParser :: Parser (Syntax Text) (Record DefaultFields)
|
||||
lineByLineParser SourceBlob{..} = pure . cofree . root $ case foldl' annotateLeaves ([], 0) lines of
|
||||
|
@ -3,6 +3,7 @@ module SemanticCmdLine (main, runDiff, runParse) where
|
||||
|
||||
import Arguments
|
||||
import Command
|
||||
import Command.Files (languageForFilePath)
|
||||
import Data.Functor.Both
|
||||
import Data.List.Split (splitWhen)
|
||||
import Data.String
|
||||
@ -47,14 +48,14 @@ main = do
|
||||
runDiff :: DiffArguments -> IO ByteString
|
||||
runDiff DiffArguments{..} = do
|
||||
blobs <- runCommand $ case diffMode of
|
||||
DiffPaths a b -> pure <$> traverse readFile (both a b)
|
||||
DiffPaths a b -> pure <$> traverse (uncurry readFile) (both a b)
|
||||
DiffCommits sha1 sha2 paths -> readFilesAtSHAs gitDir alternateObjectDirs paths (both sha1 sha2)
|
||||
Semantic.diffBlobPairs diffRenderer blobs
|
||||
|
||||
runParse :: ParseArguments -> IO ByteString
|
||||
runParse ParseArguments{..} = do
|
||||
blobs <- runCommand $ case parseMode of
|
||||
ParsePaths paths -> traverse readFile paths
|
||||
ParsePaths paths -> traverse (uncurry readFile) paths
|
||||
ParseCommit sha paths -> readFilesAtSHA gitDir alternateObjectDirs paths sha
|
||||
Semantic.parseBlobs parseTreeRenderer blobs
|
||||
|
||||
@ -79,12 +80,12 @@ arguments gitDir alternates = info (version <*> helper <*> argumentsParser) desc
|
||||
<|> flag' sExpressionDiff (long "sexpression" <> help "Output an s-expression diff tree")
|
||||
<|> flag' tocDiff (long "toc" <> help "Output a table of contents diff summary") )
|
||||
<*> ( DiffPaths
|
||||
<$> argument str (metavar "FILE_A")
|
||||
<*> argument str (metavar "FILE_B")
|
||||
<$> argument filePathReader (metavar "FILE_A")
|
||||
<*> argument filePathReader (metavar "FILE_B")
|
||||
<|> DiffCommits
|
||||
<$> option (eitherReader parseSha) (long "sha1" <> metavar "SHA" <> help "Starting commit SHA")
|
||||
<*> option (eitherReader parseSha) (long "sha2" <> metavar "SHA" <> help "Ending commit SHA")
|
||||
<*> many (argument str (metavar "FILES...")) )
|
||||
<*> many (argument filePathReader (metavar "FILES...")) )
|
||||
<*> pure gitDir
|
||||
<*> pure alternates )
|
||||
|
||||
@ -93,10 +94,10 @@ arguments gitDir alternates = info (version <*> helper <*> argumentsParser) desc
|
||||
<$> ( ( flag sExpressionParseTree sExpressionParseTree (long "sexpression" <> help "Output s-expression parse trees (default)")
|
||||
<|> flag' jsonParseTree (long "json" <> help "Output JSON parse trees") )
|
||||
<*> ( ParsePaths
|
||||
<$> some (argument str (metavar "FILES..."))
|
||||
<$> some (argument filePathReader (metavar "FILES..."))
|
||||
<|> ParseCommit
|
||||
<$> option (eitherReader parseSha) (long "sha" <> metavar "SHA" <> help "Commit SHA")
|
||||
<*> some (argument str (metavar "FILES...")) )
|
||||
<*> some (argument filePathReader (metavar "FILES...")) )
|
||||
<*> pure gitDir
|
||||
<*> pure alternates )
|
||||
|
||||
@ -105,3 +106,10 @@ arguments gitDir alternates = info (version <*> helper <*> argumentsParser) desc
|
||||
Just [sha] -> Right sha
|
||||
_ -> Left $ s <> " is not a valid SHA-1"
|
||||
where regex = mkRegexWithOpts "([0-9a-f]{40})" True False
|
||||
|
||||
filePathReader = eitherReader parseFilePath
|
||||
parseFilePath arg = case splitWhen (== ':') arg of
|
||||
[a, b] | Just lang <- readMaybe a -> Right (b, Just lang)
|
||||
| Just lang <- readMaybe b -> Right (a, Just lang)
|
||||
[path] -> Right (path, languageForFilePath path)
|
||||
_ -> Left ("cannot parse `" <> arg <> "`\nexpecting LANGUAGE:FILE or just FILE")
|
||||
|
@ -5,6 +5,7 @@ module Source where
|
||||
import qualified Data.ByteString as B
|
||||
import Data.String (IsString(..))
|
||||
import qualified Data.Text as T
|
||||
import Language
|
||||
import Numeric
|
||||
import Range
|
||||
import Prologue
|
||||
@ -18,6 +19,7 @@ data SourceBlob = SourceBlob
|
||||
, oid :: T.Text -- ^ 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.
|
||||
@ -38,7 +40,7 @@ defaultPlainBlob :: SourceKind
|
||||
defaultPlainBlob = PlainBlob 0o100644
|
||||
|
||||
emptySourceBlob :: FilePath -> SourceBlob
|
||||
emptySourceBlob filepath = SourceBlob Source.empty Source.nullOid filepath Nothing
|
||||
emptySourceBlob filepath = SourceBlob Source.empty Source.nullOid filepath Nothing Nothing
|
||||
|
||||
nullBlob :: SourceBlob -> Bool
|
||||
nullBlob SourceBlob{..} = oid == nullOid || Source.null source
|
||||
@ -46,8 +48,8 @@ nullBlob SourceBlob{..} = oid == nullOid || Source.null source
|
||||
nonExistentBlob :: SourceBlob -> Bool
|
||||
nonExistentBlob SourceBlob{..} = isNothing blobKind
|
||||
|
||||
sourceBlob :: Source -> FilePath -> SourceBlob
|
||||
sourceBlob source filepath = SourceBlob source Source.nullOid filepath (Just defaultPlainBlob)
|
||||
sourceBlob :: FilePath -> Maybe Language -> Source -> SourceBlob
|
||||
sourceBlob filepath language source = SourceBlob source Source.nullOid filepath (Just defaultPlainBlob) language
|
||||
|
||||
-- | Map blobs with Nothing blobKind to empty blobs.
|
||||
idOrEmptySourceBlob :: SourceBlob -> SourceBlob
|
||||
|
@ -8,6 +8,7 @@ import Data.Map
|
||||
import Data.Maybe
|
||||
import Data.String
|
||||
import Info (DefaultFields)
|
||||
import Language
|
||||
import Prologue hiding (readFile, toList)
|
||||
import qualified Data.Vector as V
|
||||
import qualified Git.Types as Git
|
||||
@ -21,25 +22,25 @@ spec :: Spec
|
||||
spec = parallel $ do
|
||||
describe "readFile" $ do
|
||||
it "returns a blob for extant files" $ do
|
||||
blob <- runCommand (readFile "semantic-diff.cabal")
|
||||
blob <- runCommand (readFile "semantic-diff.cabal" Nothing)
|
||||
path blob `shouldBe` "semantic-diff.cabal"
|
||||
|
||||
it "returns a nullBlob for absent files" $ do
|
||||
blob <- runCommand (readFile "this file should not exist")
|
||||
blob <- runCommand (readFile "this file should not exist" Nothing)
|
||||
nullBlob blob `shouldBe` True
|
||||
|
||||
describe "readFilesAtSHA" $ do
|
||||
it "returns blobs for the specified paths" $ do
|
||||
blobs <- runCommand (readFilesAtSHA repoPath [] ["methods.rb"] (Both.snd (shas methodsFixture)))
|
||||
blobs <- runCommand (readFilesAtSHA repoPath [] [("methods.rb", Just Ruby)] (Both.snd (shas methodsFixture)))
|
||||
blobs `shouldBe` [methodsBlob]
|
||||
|
||||
it "returns emptySourceBlob if path doesn't exist at sha" $ do
|
||||
blobs <- runCommand (readFilesAtSHA repoPath [] ["methods.rb"] (Both.fst (shas methodsFixture)))
|
||||
blobs <- runCommand (readFilesAtSHA repoPath [] [("methods.rb", Just Ruby)] (Both.fst (shas methodsFixture)))
|
||||
nonExistentBlob <$> blobs `shouldBe` [True]
|
||||
|
||||
describe "readFilesAtSHAs" $ do
|
||||
it "returns blobs for the specified paths" $ do
|
||||
blobs <- runCommand (readFilesAtSHAs repoPath [] ["methods.rb"] (shas methodsFixture))
|
||||
blobs <- runCommand (readFilesAtSHAs repoPath [] [("methods.rb", Just Ruby)] (shas methodsFixture))
|
||||
blobs `shouldBe` expectedBlobs methodsFixture
|
||||
|
||||
it "returns blobs for all paths if none are specified" $ do
|
||||
@ -47,18 +48,18 @@ spec = parallel $ do
|
||||
blobs `shouldBe` expectedBlobs methodsFixture
|
||||
|
||||
it "returns entries for missing paths" $ do
|
||||
blobs <- runCommand (readFilesAtSHAs repoPath [] ["this file should not exist"] (shas methodsFixture))
|
||||
blobs <- runCommand (readFilesAtSHAs repoPath [] [("this file should not exist", Nothing)] (shas methodsFixture))
|
||||
let b = emptySourceBlob "this file should not exist"
|
||||
blobs `shouldBe` [both b b]
|
||||
|
||||
describe "fetchDiffs" $ do
|
||||
it "generates diff summaries for two shas" $ do
|
||||
(errors, summaries) <- fetchDiffsOutput summaryText "test/fixtures/git/examples/all-languages.git" "dfac8fd681b0749af137aebf3203e77a06fbafc2" "2e4144eb8c44f007463ec34cb66353f0041161fe" ["methods.rb"] Renderer.SummaryRenderer
|
||||
(errors, summaries) <- fetchDiffsOutput summaryText "test/fixtures/git/examples/all-languages.git" "dfac8fd681b0749af137aebf3203e77a06fbafc2" "2e4144eb8c44f007463ec34cb66353f0041161fe" [("methods.rb", Just Ruby)] Renderer.SummaryRenderer
|
||||
errors `shouldBe` Just (fromList [])
|
||||
summaries `shouldBe` Just (fromList [("methods.rb", ["Added the 'foo()' method"])])
|
||||
|
||||
it "generates toc summaries for two shas" $ do
|
||||
(errors, summaries) <- fetchDiffsOutput termText "test/fixtures/git/examples/all-languages.git" "dfac8fd681b0749af137aebf3203e77a06fbafc2" "2e4144eb8c44f007463ec34cb66353f0041161fe" ["methods.rb"] Renderer.ToCRenderer
|
||||
(errors, summaries) <- fetchDiffsOutput termText "test/fixtures/git/examples/all-languages.git" "dfac8fd681b0749af137aebf3203e77a06fbafc2" "2e4144eb8c44f007463ec34cb66353f0041161fe" [("methods.rb", Just Ruby)] Renderer.ToCRenderer
|
||||
errors `shouldBe` Just (fromList [])
|
||||
summaries `shouldBe` Just (fromList [("methods.rb", ["foo"])])
|
||||
|
||||
@ -68,22 +69,22 @@ spec = parallel $ do
|
||||
summaries `shouldBe` Just (fromList [("methods.rb", ["foo"])])
|
||||
|
||||
it "errors with bad shas" $
|
||||
fetchDiffsOutput summaryText "test/fixtures/git/examples/all-languages.git" "dead" "beef" ["methods.rb"] Renderer.SummaryRenderer
|
||||
fetchDiffsOutput summaryText "test/fixtures/git/examples/all-languages.git" "dead" "beef" [("methods.rb", Just Ruby)] Renderer.SummaryRenderer
|
||||
`shouldThrow` (== Git.BackendError "Could not lookup dead: Object not found - no match for prefix (dead000000000000000000000000000000000000)")
|
||||
|
||||
it "errors with bad repo path" $
|
||||
fetchDiffsOutput summaryText "test/fixtures/git/examples/not-a-repo.git" "dfac8fd681b0749af137aebf3203e77a06fbafc2" "2e4144eb8c44f007463ec34cb66353f0041161fe" ["methods.rb"] Renderer.SummaryRenderer
|
||||
fetchDiffsOutput summaryText "test/fixtures/git/examples/not-a-repo.git" "dfac8fd681b0749af137aebf3203e77a06fbafc2" "2e4144eb8c44f007463ec34cb66353f0041161fe" [("methods.rb", Just Ruby)] Renderer.SummaryRenderer
|
||||
`shouldThrow` errorCall "Could not open repository \"test/fixtures/git/examples/not-a-repo.git\""
|
||||
|
||||
where repoPath = "test/fixtures/git/examples/all-languages.git"
|
||||
methodsFixture = Fixture
|
||||
(both "dfac8fd681b0749af137aebf3203e77a06fbafc2" "2e4144eb8c44f007463ec34cb66353f0041161fe")
|
||||
[ both (emptySourceBlob "methods.rb") methodsBlob ]
|
||||
methodsBlob = SourceBlob (Source "def foo\nend\n") "ff7bbbe9495f61d9e1e58c597502d152bab1761e" "methods.rb" (Just defaultPlainBlob)
|
||||
methodsBlob = SourceBlob (Source "def foo\nend\n") "ff7bbbe9495f61d9e1e58c597502d152bab1761e" "methods.rb" (Just defaultPlainBlob) (Just Ruby)
|
||||
|
||||
data Fixture = Fixture { shas :: Both String, expectedBlobs :: [Both SourceBlob] }
|
||||
|
||||
fetchDiffsOutput :: (Object -> Text) -> FilePath -> String -> String -> [FilePath] -> DiffRenderer DefaultFields Summaries -> IO (Maybe (Map Text Value), Maybe (Map Text [Text]))
|
||||
fetchDiffsOutput :: (Object -> Text) -> FilePath -> String -> String -> [(FilePath, Maybe Language)] -> DiffRenderer DefaultFields Summaries -> IO (Maybe (Map Text Value), Maybe (Map Text [Text]))
|
||||
fetchDiffsOutput f gitDir sha1 sha2 filePaths renderer = do
|
||||
blobs <- runCommand $ readFilesAtSHAs gitDir [] filePaths (both sha1 sha2)
|
||||
results <- Semantic.diffBlobPairs renderer blobs
|
||||
|
@ -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)) (SourceBlob Source.empty "xyz" "path2.txt" (Just defaultPlainBlob))) `shouldBe` [Hunk {offset = pure 0, changes = [], trailingContext = []}]
|
||||
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 = []}]
|
||||
|
@ -3,6 +3,7 @@ module SemanticCmdLineSpec where
|
||||
|
||||
import Prologue
|
||||
import Arguments
|
||||
import Language
|
||||
import SemanticCmdLine
|
||||
import Data.Functor.Listable
|
||||
import Test.Hspec hiding (shouldBe, shouldNotBe, shouldThrow, errorCall)
|
||||
@ -38,13 +39,13 @@ instance Listable ParseFixture where
|
||||
\/ cons0 (ParseFixture (jsonParseTree commitMode repo []) jsonParseTreeOutput'')
|
||||
\/ cons0 (ParseFixture (jsonParseTree (ParseCommit "2e4144eb8c44f007463ec34cb66353f0041161fe" []) repo []) emptyJsonParseTreeOutput)
|
||||
\/ cons0 (ParseFixture (jsonParseTree (ParsePaths []) repo []) emptyJsonParseTreeOutput)
|
||||
\/ cons0 (ParseFixture (jsonParseTree (ParseCommit "2e4144eb8c44f007463ec34cb66353f0041161fe" ["not-a-file.rb"]) repo []) emptyJsonParseTreeOutput)
|
||||
\/ cons0 (ParseFixture (jsonParseTree (ParsePaths ["not-a-file.rb"]) repo []) emptyJsonParseTreeOutput)
|
||||
\/ cons0 (ParseFixture (jsonParseTree (ParseCommit "2e4144eb8c44f007463ec34cb66353f0041161fe" [("not-a-file.rb", Just Ruby)]) repo []) emptyJsonParseTreeOutput)
|
||||
\/ cons0 (ParseFixture (jsonParseTree (ParsePaths [("not-a-file.rb", Just Ruby)]) repo []) emptyJsonParseTreeOutput)
|
||||
|
||||
where
|
||||
pathMode = ParsePaths ["test/fixtures/ruby/and-or.A.rb"]
|
||||
pathMode' = ParsePaths ["test/fixtures/ruby/and-or.A.rb", "test/fixtures/ruby/and-or.B.rb"]
|
||||
commitMode = ParseCommit "2e4144eb8c44f007463ec34cb66353f0041161fe" ["methods.rb"]
|
||||
pathMode = ParsePaths [("test/fixtures/ruby/and-or.A.rb", Just Ruby)]
|
||||
pathMode' = ParsePaths [("test/fixtures/ruby/and-or.A.rb", Just Ruby), ("test/fixtures/ruby/and-or.B.rb", Just Ruby)]
|
||||
commitMode = ParseCommit "2e4144eb8c44f007463ec34cb66353f0041161fe" [("methods.rb", Just Ruby)]
|
||||
|
||||
sExpressionParseTreeOutput = "(Program\n (Binary\n (Identifier)\n (Other \"and\")\n (Identifier)))\n"
|
||||
jsonParseTreeOutput = "[{\"filePath\":\"test/fixtures/ruby/and-or.A.rb\",\"programNode\":{\"category\":\"Program\",\"children\":[{\"category\":\"Binary\",\"children\":[{\"category\":\"Identifier\",\"children\":[],\"sourceRange\":[0,3],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,4]}},{\"category\":\"and\",\"children\":[],\"sourceRange\":[4,7],\"sourceSpan\":{\"start\":[1,5],\"end\":[1,8]}},{\"category\":\"Identifier\",\"children\":[],\"sourceRange\":[8,11],\"sourceSpan\":{\"start\":[1,9],\"end\":[1,12]}}],\"sourceRange\":[0,11],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,12]}}],\"sourceRange\":[0,12],\"sourceSpan\":{\"start\":[1,1],\"end\":[2,1]}}}]\n"
|
||||
@ -71,8 +72,8 @@ instance Listable DiffFixture where
|
||||
\/ cons0 (DiffFixture (tocDiff commitMode repo []) tocOutput')
|
||||
|
||||
where
|
||||
pathMode = DiffPaths "test/fixtures/ruby/method-declaration.A.rb" "test/fixtures/ruby/method-declaration.B.rb"
|
||||
commitMode = DiffCommits "dfac8fd681b0749af137aebf3203e77a06fbafc2" "2e4144eb8c44f007463ec34cb66353f0041161fe" ["methods.rb"]
|
||||
pathMode = DiffPaths ("test/fixtures/ruby/method-declaration.A.rb", Just Ruby) ("test/fixtures/ruby/method-declaration.B.rb", Just Ruby)
|
||||
commitMode = DiffCommits "dfac8fd681b0749af137aebf3203e77a06fbafc2" "2e4144eb8c44f007463ec34cb66353f0041161fe" [("methods.rb", Just Ruby)]
|
||||
|
||||
patchOutput = "diff --git a/test/fixtures/ruby/method-declaration.A.rb b/test/fixtures/ruby/method-declaration.B.rb\nindex 0000000000000000000000000000000000000000..0000000000000000000000000000000000000000 100644\n--- a/test/fixtures/ruby/method-declaration.A.rb\n+++ b/test/fixtures/ruby/method-declaration.B.rb\n@@ -1,3 +1,4 @@\n-def foo\n+def bar(a)\n+ baz\n end\n\n"
|
||||
patchOutput' = "diff --git a/methods.rb b/methods.rb\nnew file mode 100644\nindex 0000000000000000000000000000000000000000..ff7bbbe9495f61d9e1e58c597502d152bab1761e\n--- /dev/null\n+++ b/methods.rb\n+def foo\n+end\n\n"
|
||||
|
@ -4,6 +4,7 @@ import Prologue
|
||||
import Semantic
|
||||
import Test.Hspec hiding (shouldBe, shouldNotBe, shouldThrow, errorCall)
|
||||
import Test.Hspec.Expectations.Pretty
|
||||
import Language
|
||||
import Syntax
|
||||
import Renderer
|
||||
import Renderer.SExpression
|
||||
@ -17,7 +18,7 @@ spec = parallel $ do
|
||||
void term `shouldBe` cofree (() :< Indexed [ cofree (() :< Method [] (cofree (() :< Leaf "foo")) Nothing [] []) ])
|
||||
|
||||
it "parses line by line if not given a language" $ do
|
||||
term <- parseBlob methodsBlob { path = "methods" }
|
||||
term <- parseBlob methodsBlob { blobLanguage = Nothing }
|
||||
void term `shouldBe` cofree (() :< Indexed [ cofree (() :< Leaf "def foo\n"), cofree (() :< Leaf "end\n"), cofree (() :< Leaf "") ])
|
||||
|
||||
describe "parseBlobs" $ do
|
||||
@ -26,4 +27,4 @@ spec = parallel $ do
|
||||
output `shouldBe` "(Program\n (Method\n (Identifier)))\n"
|
||||
|
||||
where
|
||||
methodsBlob = SourceBlob (Source "def foo\nend\n") "ff7bbbe9495f61d9e1e58c597502d152bab1761e" "methods.rb" (Just defaultPlainBlob)
|
||||
methodsBlob = SourceBlob (Source "def foo\nend\n") "ff7bbbe9495f61d9e1e58c597502d152bab1761e" "methods.rb" (Just defaultPlainBlob) (Just Ruby)
|
||||
|
@ -2,15 +2,12 @@
|
||||
module SpecHelpers
|
||||
( diffFilePaths
|
||||
, parseFilePath
|
||||
, readFileToUnicode
|
||||
, parserForFilePath
|
||||
, readFile
|
||||
, languageForFilePath
|
||||
) where
|
||||
|
||||
import Data.Functor.Both
|
||||
import Data.Record
|
||||
import Info
|
||||
import Language
|
||||
import Parser
|
||||
import Prologue hiding (readFile)
|
||||
import qualified Data.ByteString as B
|
||||
import qualified Data.Text.ICU.Convert as Convert
|
||||
@ -19,7 +16,6 @@ import Renderer
|
||||
import Renderer.SExpression
|
||||
import Semantic
|
||||
import Source
|
||||
import Syntax
|
||||
import System.FilePath
|
||||
|
||||
-- | Returns an s-expression formatted diff for the specified FilePath pair.
|
||||
@ -31,26 +27,8 @@ diffFilePaths paths = do
|
||||
-- | Returns an s-expression parse tree for the specified FilePath.
|
||||
parseFilePath :: FilePath -> IO ByteString
|
||||
parseFilePath path = do
|
||||
source <- readFileToUnicode path
|
||||
parseBlobs (SExpressionParseTreeRenderer TreeOnly) [sourceBlob source path]
|
||||
|
||||
-- | Read a file, convert it's contents unicode and return it wrapped in Source.
|
||||
readFileToUnicode :: FilePath -> IO Source
|
||||
readFileToUnicode path = B.readFile path >>= transcode
|
||||
where
|
||||
transcode :: B.ByteString -> IO Source
|
||||
transcode text = fromText <$> do
|
||||
match <- Detect.detectCharset text
|
||||
converter <- Convert.open match Nothing
|
||||
pure $ Convert.toUnicode converter text
|
||||
|
||||
-- | Return a parser based on the FilePath's extension (including the ".").
|
||||
--
|
||||
-- NB: This is intentionally duplicated from Parser.Language because our tests
|
||||
-- will always need to be able to select language from file extention whereas
|
||||
-- the semantic project should eventually depend on external language detection.
|
||||
parserForFilePath :: FilePath -> Parser (Syntax Text) (Record DefaultFields)
|
||||
parserForFilePath = parserForLanguage . languageForType . toS . takeExtension
|
||||
blob <- readFile path
|
||||
parseBlobs (SExpressionParseTreeRenderer TreeOnly) [blob]
|
||||
|
||||
-- | Read a file to a SourceBlob.
|
||||
--
|
||||
@ -60,4 +38,18 @@ parserForFilePath = parserForLanguage . languageForType . toS . takeExtension
|
||||
readFile :: FilePath -> IO SourceBlob
|
||||
readFile path = do
|
||||
source <- (Just <$> readFileToUnicode path) `catch` (const (pure Nothing) :: IOException -> IO (Maybe Source))
|
||||
pure $ fromMaybe (emptySourceBlob path) (flip sourceBlob path <$> source)
|
||||
pure $ fromMaybe (emptySourceBlob path) (sourceBlob path (languageForFilePath path) <$> source)
|
||||
where
|
||||
-- | Read a file, convert it's contents unicode and return it wrapped in Source.
|
||||
readFileToUnicode :: FilePath -> IO Source
|
||||
readFileToUnicode path = B.readFile path >>= transcode
|
||||
where
|
||||
transcode :: B.ByteString -> IO Source
|
||||
transcode text = fromText <$> do
|
||||
match <- Detect.detectCharset text
|
||||
converter <- Convert.open match Nothing
|
||||
pure $ Convert.toUnicode converter text
|
||||
|
||||
-- | Returns a Maybe Language based on the FilePath's extension.
|
||||
languageForFilePath :: FilePath -> Maybe Language
|
||||
languageForFilePath = languageForType . toS . takeExtension
|
||||
|
@ -9,6 +9,7 @@ import RWS
|
||||
import Data.Record
|
||||
import Data.String
|
||||
import Diff
|
||||
import Language
|
||||
import Renderer.Summary
|
||||
import Info
|
||||
import Interpreter
|
||||
@ -41,7 +42,7 @@ replacementSummary :: DiffSummary DiffInfo
|
||||
replacementSummary = DiffSummary { diffSummaryPatch = Replace (LeafInfo StringLiteral "a" $ sourceSpanBetween (1, 2) (1, 4)) (LeafInfo SymbolLiteral "b" $ sourceSpanBetween (1,1) (1, 2)), parentAnnotation = [Left (Info.FunctionCall, "foo")] }
|
||||
|
||||
blobs :: Both SourceBlob
|
||||
blobs = both (SourceBlob (fromText "[]") nullOid "a.js" (Just defaultPlainBlob)) (SourceBlob (fromText "[a]") nullOid "b.js" (Just defaultPlainBlob))
|
||||
blobs = both (SourceBlob (fromText "[]") nullOid "a.js" (Just defaultPlainBlob) (Just JavaScript)) (SourceBlob (fromText "[a]") nullOid "b.js" (Just defaultPlainBlob) (Just JavaScript))
|
||||
|
||||
spec :: Spec
|
||||
spec = parallel $ do
|
||||
|
@ -11,8 +11,9 @@ import Data.String
|
||||
import Diff
|
||||
import Info
|
||||
import Interpreter
|
||||
import Language
|
||||
import Patch
|
||||
import Prologue hiding (fst, snd)
|
||||
import Prologue hiding (fst, snd, readFile)
|
||||
import Renderer
|
||||
import Renderer.TOC
|
||||
import Source
|
||||
@ -111,12 +112,12 @@ spec = parallel $ do
|
||||
it "produces JSON output" $ do
|
||||
blobs <- blobsForPaths (both "ruby/methods.A.rb" "ruby/methods.B.rb")
|
||||
output <- diffBlobPairs ToCRenderer [blobs]
|
||||
output `shouldBe` "{\"changes\":{\"ruby/methods.A.rb -> ruby/methods.B.rb\":[{\"span\":{\"start\":[1,1],\"end\":[2,4]},\"category\":\"Method\",\"term\":\"self.foo\",\"changeType\":\"added\"},{\"span\":{\"start\":[4,1],\"end\":[6,4]},\"category\":\"Method\",\"term\":\"bar\",\"changeType\":\"modified\"},{\"span\":{\"start\":[4,1],\"end\":[5,4]},\"category\":\"Method\",\"term\":\"baz\",\"changeType\":\"removed\"}]},\"errors\":{}}\n"
|
||||
output `shouldBe` "{\"changes\":{\"test/fixtures/toc/ruby/methods.A.rb -> test/fixtures/toc/ruby/methods.B.rb\":[{\"span\":{\"start\":[1,1],\"end\":[2,4]},\"category\":\"Method\",\"term\":\"self.foo\",\"changeType\":\"added\"},{\"span\":{\"start\":[4,1],\"end\":[6,4]},\"category\":\"Method\",\"term\":\"bar\",\"changeType\":\"modified\"},{\"span\":{\"start\":[4,1],\"end\":[5,4]},\"category\":\"Method\",\"term\":\"baz\",\"changeType\":\"removed\"}]},\"errors\":{}}\n"
|
||||
|
||||
it "produces JSON output if there are parse errors" $ do
|
||||
blobs <- blobsForPaths (both "ruby/methods.A.rb" "ruby/methods.X.rb")
|
||||
output <- diffBlobPairs ToCRenderer [blobs]
|
||||
output `shouldBe` "{\"changes\":{},\"errors\":{\"ruby/methods.A.rb -> ruby/methods.X.rb\":[{\"span\":{\"start\":[1,1],\"end\":[3,1]},\"error\":\"def bar\\nen\\n\"}]}}\n"
|
||||
output `shouldBe` "{\"changes\":{},\"errors\":{\"test/fixtures/toc/ruby/methods.A.rb -> test/fixtures/toc/ruby/methods.X.rb\":[{\"span\":{\"start\":[1,1],\"end\":[3,1]},\"error\":\"def bar\\nen\\n\"}]}}\n"
|
||||
|
||||
type Diff' = SyntaxDiff String DefaultFields
|
||||
type Term' = SyntaxTerm String DefaultFields
|
||||
@ -182,9 +183,7 @@ isMethodOrFunction a = case runCofree (unListableF a) of
|
||||
_ -> False
|
||||
|
||||
blobsForPaths :: Both FilePath -> IO (Both SourceBlob)
|
||||
blobsForPaths paths = do
|
||||
sources <- traverse (readFileToUnicode . ("test/fixtures/toc/" <>)) paths
|
||||
pure $ SourceBlob <$> sources <*> pure mempty <*> paths <*> pure (Just Source.defaultPlainBlob)
|
||||
blobsForPaths = traverse (readFile . ("test/fixtures/toc/" <>))
|
||||
|
||||
sourceSpanBetween :: (Int, Int) -> (Int, Int) -> SourceSpan
|
||||
sourceSpanBetween (s1, e1) (s2, e2) = SourceSpan (SourcePos s1 e1) (SourcePos s2 e2)
|
||||
@ -196,7 +195,7 @@ blankDiff = free $ Free (pure arrayInfo :< Indexed [ free $ Pure (Insert (cofree
|
||||
literalInfo = StringLiteral :. Range 1 2 :. sourceSpanBetween (1, 2) (1, 4) :. Nil
|
||||
|
||||
blankDiffBlobs :: Both SourceBlob
|
||||
blankDiffBlobs = both (SourceBlob (fromText "[]") nullOid "a.js" (Just defaultPlainBlob)) (SourceBlob (fromText "[a]") nullOid "b.js" (Just defaultPlainBlob))
|
||||
blankDiffBlobs = both (SourceBlob (fromText "[]") nullOid "a.js" (Just defaultPlainBlob) (Just JavaScript)) (SourceBlob (fromText "[a]") nullOid "b.js" (Just defaultPlainBlob) (Just JavaScript))
|
||||
|
||||
unListableDiff :: Functor f => ListableF (Free (TermF f (ListableF (Join (,)) annotation))) (Patch (ListableF (Term f) annotation)) -> Diff f annotation
|
||||
unListableDiff diff = hoistFree (first unListableF) $ fmap unListableF <$> unListableF diff
|
||||
|
2
vendor/hspec-expectations-pretty-diff
vendored
2
vendor/hspec-expectations-pretty-diff
vendored
@ -1 +1 @@
|
||||
Subproject commit 8762cd516394091b20f8b7e041e3ca29bd3aec90
|
||||
Subproject commit 94af5871c24ba319f7f72fefa53c1a4d074c9a29
|
Loading…
Reference in New Issue
Block a user