Add dependency tracking
This commit is contained in:
parent
39ae809118
commit
e3d6117590
@ -29,6 +29,8 @@ import Handler.Shared (gitPath)
|
|||||||
|
|
||||||
import "Glob" System.FilePath.Glob as G
|
import "Glob" System.FilePath.Glob as G
|
||||||
|
|
||||||
|
import PersistSHA1
|
||||||
|
|
||||||
data ExtractionOptions = ExtractionOptions {
|
data ExtractionOptions = ExtractionOptions {
|
||||||
extractionOptionsDescription :: Maybe Text,
|
extractionOptionsDescription :: Maybe Text,
|
||||||
extractionOptionsTags :: Maybe (S.Set Text),
|
extractionOptionsTags :: Maybe (S.Set Text),
|
||||||
@ -36,8 +38,9 @@ data ExtractionOptions = ExtractionOptions {
|
|||||||
extractionOptionsUnwantedParams :: Maybe [Text],
|
extractionOptionsUnwantedParams :: Maybe [Text],
|
||||||
extractionOptionsParamFiles :: Maybe [String],
|
extractionOptionsParamFiles :: Maybe [String],
|
||||||
extractionOptionsMLRunPath :: Maybe FilePath,
|
extractionOptionsMLRunPath :: Maybe FilePath,
|
||||||
extractionOptionsExternalLinks :: Maybe [Link]
|
extractionOptionsExternalLinks :: Maybe [Link],
|
||||||
}
|
extractionOptionsDependencies :: Maybe [SHA1]
|
||||||
|
}
|
||||||
|
|
||||||
instance FromJSON ExtractionOptions where
|
instance FromJSON ExtractionOptions where
|
||||||
parseJSON = withObject "ExtractionOptions" $ \v -> ExtractionOptions
|
parseJSON = withObject "ExtractionOptions" $ \v -> ExtractionOptions
|
||||||
@ -48,6 +51,7 @@ instance FromJSON ExtractionOptions where
|
|||||||
<*> v .:? "param-files"
|
<*> v .:? "param-files"
|
||||||
<*> v .:? "mlrun-path"
|
<*> v .:? "mlrun-path"
|
||||||
<*> v .:? "links"
|
<*> v .:? "links"
|
||||||
|
<*> fmap (fmap (Import.map fromTextToSHA1)) (v .:? "dependencies")
|
||||||
|
|
||||||
instance Default ExtractionOptions where
|
instance Default ExtractionOptions where
|
||||||
def = ExtractionOptions {
|
def = ExtractionOptions {
|
||||||
@ -57,7 +61,8 @@ instance Default ExtractionOptions where
|
|||||||
extractionOptionsUnwantedParams = Nothing,
|
extractionOptionsUnwantedParams = Nothing,
|
||||||
extractionOptionsParamFiles = Nothing,
|
extractionOptionsParamFiles = Nothing,
|
||||||
extractionOptionsMLRunPath = Nothing,
|
extractionOptionsMLRunPath = Nothing,
|
||||||
extractionOptionsExternalLinks = Nothing
|
extractionOptionsExternalLinks = Nothing,
|
||||||
|
extractionOptionsDependencies = Nothing
|
||||||
}
|
}
|
||||||
|
|
||||||
data Link = Link {
|
data Link = Link {
|
||||||
@ -74,7 +79,8 @@ data GonitoMetadata = GonitoMetadata {
|
|||||||
gonitoMetadataDescription :: Text,
|
gonitoMetadataDescription :: Text,
|
||||||
gonitoMetadataTags :: S.Set Text,
|
gonitoMetadataTags :: S.Set Text,
|
||||||
gonitoMetadataGeneralParams :: M.Map Text Text,
|
gonitoMetadataGeneralParams :: M.Map Text Text,
|
||||||
gonitoMetadataExternalLinks :: [Link]
|
gonitoMetadataExternalLinks :: [Link],
|
||||||
|
gonitoMetadataDependencies :: [SHA1]
|
||||||
}
|
}
|
||||||
deriving (Eq, Show)
|
deriving (Eq, Show)
|
||||||
|
|
||||||
@ -102,7 +108,11 @@ combineExtractionOptions (Just otherOptions) options = ExtractionOptions {
|
|||||||
extractionOptionsMLRunPath = combineWithF extractionOptionsMLRunPath,
|
extractionOptionsMLRunPath = combineWithF extractionOptionsMLRunPath,
|
||||||
extractionOptionsExternalLinks = case extractionOptionsExternalLinks options of
|
extractionOptionsExternalLinks = case extractionOptionsExternalLinks options of
|
||||||
Nothing -> extractionOptionsExternalLinks otherOptions
|
Nothing -> extractionOptionsExternalLinks otherOptions
|
||||||
Just links -> Just (links ++ (fromMaybe [] $ extractionOptionsExternalLinks otherOptions)) }
|
Just links -> Just (links ++ (fromMaybe [] $ extractionOptionsExternalLinks otherOptions)),
|
||||||
|
extractionOptionsDependencies = case extractionOptionsDependencies options of
|
||||||
|
Nothing -> extractionOptionsDependencies otherOptions
|
||||||
|
Just links -> Just (links ++ (fromMaybe [] $ extractionOptionsDependencies otherOptions)) }
|
||||||
|
|
||||||
where combineWithT fun = case fun options of
|
where combineWithT fun = case fun options of
|
||||||
Nothing -> fun otherOptions
|
Nothing -> fun otherOptions
|
||||||
Just v -> Just v
|
Just v -> Just v
|
||||||
@ -146,13 +156,28 @@ extractMetadataFromRepoDir repoDir formExtractionOptions = do
|
|||||||
`M.union`
|
`M.union`
|
||||||
fromMaybe M.empty (extractionOptionsGeneralParams extractionOptions)
|
fromMaybe M.empty (extractionOptionsGeneralParams extractionOptions)
|
||||||
|
|
||||||
|
let dependenciesFromYaml = fromMaybe [] $ extractionOptionsDependencies extractionOptions
|
||||||
|
dependenciesFromGitSubmodules <- extractDependenciesFromGitSubmodules repoDir
|
||||||
|
|
||||||
pure $ GonitoMetadata {
|
pure $ GonitoMetadata {
|
||||||
gonitoMetadataDescription = description,
|
gonitoMetadataDescription = description,
|
||||||
gonitoMetadataTags = tagsParsed,
|
gonitoMetadataTags = tagsParsed,
|
||||||
gonitoMetadataGeneralParams = params,
|
gonitoMetadataGeneralParams = params,
|
||||||
gonitoMetadataExternalLinks = fromMaybe [] (extractionOptionsExternalLinks extractionOptions)
|
gonitoMetadataExternalLinks = fromMaybe [] (extractionOptionsExternalLinks extractionOptions),
|
||||||
|
gonitoMetadataDependencies = dependenciesFromYaml ++ dependenciesFromGitSubmodules
|
||||||
}
|
}
|
||||||
|
|
||||||
|
extractDependenciesFromGitSubmodules :: FilePath -> IO [SHA1]
|
||||||
|
extractDependenciesFromGitSubmodules repoDir = do
|
||||||
|
(exitCode, out) <- runProgram repoDir gitPath ["submodule"]
|
||||||
|
return $ case exitCode of
|
||||||
|
ExitSuccess -> Import.map (fromTextToSHA1
|
||||||
|
. Data.Text.take sha1Lenght
|
||||||
|
. Data.Text.drop 1)
|
||||||
|
$ Data.Text.lines out
|
||||||
|
ExitFailure _ -> []
|
||||||
|
where sha1Lenght = 40
|
||||||
|
|
||||||
|
|
||||||
parseParamFile :: FilePath -> IO (M.Map Text Text)
|
parseParamFile :: FilePath -> IO (M.Map Text Text)
|
||||||
parseParamFile yamlFile = do
|
parseParamFile yamlFile = do
|
||||||
|
@ -280,7 +280,8 @@ doCreateSubmission userId challengeId mDescription mTags repoSpec chan = do
|
|||||||
extractionOptionsUnwantedParams = Nothing,
|
extractionOptionsUnwantedParams = Nothing,
|
||||||
extractionOptionsParamFiles = Nothing,
|
extractionOptionsParamFiles = Nothing,
|
||||||
extractionOptionsMLRunPath = Nothing,
|
extractionOptionsMLRunPath = Nothing,
|
||||||
extractionOptionsExternalLinks = Nothing })
|
extractionOptionsExternalLinks = Nothing,
|
||||||
|
extractionOptionsDependencies = Nothing })
|
||||||
|
|
||||||
submissionId <- getSubmission userId
|
submissionId <- getSubmission userId
|
||||||
repoId
|
repoId
|
||||||
@ -294,6 +295,10 @@ doCreateSubmission userId challengeId mDescription mTags repoSpec chan = do
|
|||||||
externalLinkTitle = linkTitle l,
|
externalLinkTitle = linkTitle l,
|
||||||
externalLinkUrl = linkUrl l }) $ gonitoMetadataExternalLinks gonitoMetadata
|
externalLinkUrl = linkUrl l }) $ gonitoMetadataExternalLinks gonitoMetadata
|
||||||
|
|
||||||
|
_ <- runDB $ mapM insert $ map (\s -> Dependency {
|
||||||
|
dependencySubRepoCommit = s,
|
||||||
|
dependencySuperRepoCommit = (repoCurrentCommit repo) }) $ gonitoMetadataDependencies gonitoMetadata
|
||||||
|
|
||||||
outs <- getOuts chan submissionId (gonitoMetadataGeneralParams gonitoMetadata)
|
outs <- getOuts chan submissionId (gonitoMetadataGeneralParams gonitoMetadata)
|
||||||
|
|
||||||
currentTagIds <- runDB $ selectList [SubmissionTagSubmission ==. submissionId] []
|
currentTagIds <- runDB $ selectList [SubmissionTagSubmission ==. submissionId] []
|
||||||
|
@ -9,7 +9,7 @@ import qualified Data.Text as T
|
|||||||
import Numeric (showHex)
|
import Numeric (showHex)
|
||||||
|
|
||||||
data SHA1 = SHA1 ByteString
|
data SHA1 = SHA1 ByteString
|
||||||
deriving Show
|
deriving (Eq, Show)
|
||||||
|
|
||||||
toHex :: ByteString -> ByteString
|
toHex :: ByteString -> ByteString
|
||||||
toHex = BC.pack . concat . (map ("\\x"++)) . (map (flip showHex "")) . B.unpack
|
toHex = BC.pack . concat . (map ("\\x"++)) . (map (flip showHex "")) . B.unpack
|
||||||
|
@ -72,10 +72,23 @@ ExternalLink
|
|||||||
submission SubmissionId
|
submission SubmissionId
|
||||||
title Text Maybe
|
title Text Maybe
|
||||||
url Text
|
url Text
|
||||||
|
-- this represents forks, i.e. when a submission for a given challenge
|
||||||
|
-- was based (in terms of git history) on another submission for the same challenge
|
||||||
|
-- NOTE: not implemented yet
|
||||||
Fork
|
Fork
|
||||||
source SubmissionId
|
source SubmissionId
|
||||||
target SubmissionId
|
target SubmissionId
|
||||||
UniqueSourceTarget source target
|
UniqueSourceTarget source target
|
||||||
|
-- for representing dependencies across challenges;
|
||||||
|
-- e.g. when a model generated in a submission is used
|
||||||
|
-- by another submission in another challenge;
|
||||||
|
-- dependencies are expressed as a relation between
|
||||||
|
-- commit hashes rather than submissions/repos
|
||||||
|
-- (can be easily linked to submission via SubmissionCommit link)
|
||||||
|
Dependency
|
||||||
|
subRepoCommit SHA1
|
||||||
|
superRepoCommit SHA1
|
||||||
|
UniqueSubSuperSubmission subRepoCommit superRepoCommit
|
||||||
Evaluation
|
Evaluation
|
||||||
test TestId
|
test TestId
|
||||||
checksum SHA1
|
checksum SHA1
|
||||||
|
@ -4,6 +4,8 @@ module Gonito.ExtractMetadataSpec (spec) where
|
|||||||
|
|
||||||
import Import
|
import Import
|
||||||
|
|
||||||
|
import PersistSHA1
|
||||||
|
|
||||||
import qualified Data.Set as S
|
import qualified Data.Set as S
|
||||||
import qualified Data.Map.Strict as M
|
import qualified Data.Map.Strict as M
|
||||||
|
|
||||||
@ -18,7 +20,8 @@ spec = do
|
|||||||
gonitoMetadataDescription = "Simple solution",
|
gonitoMetadataDescription = "Simple solution",
|
||||||
gonitoMetadataTags = S.fromList ["foo", "simple-solution", "baz"],
|
gonitoMetadataTags = S.fromList ["foo", "simple-solution", "baz"],
|
||||||
gonitoMetadataGeneralParams = M.empty,
|
gonitoMetadataGeneralParams = M.empty,
|
||||||
gonitoMetadataExternalLinks = []
|
gonitoMetadataExternalLinks = [],
|
||||||
|
gonitoMetadataDependencies = []
|
||||||
}
|
}
|
||||||
it "simple with some fields from the form" $ do
|
it "simple with some fields from the form" $ do
|
||||||
extractMetadataFromRepoDir "test/fake-git-repos/simple/" def {
|
extractMetadataFromRepoDir "test/fake-git-repos/simple/" def {
|
||||||
@ -28,7 +31,8 @@ spec = do
|
|||||||
gonitoMetadataDescription = "Other solution",
|
gonitoMetadataDescription = "Other solution",
|
||||||
gonitoMetadataTags = S.fromList ["foo", "simple-solution", "baz", "other-tag"],
|
gonitoMetadataTags = S.fromList ["foo", "simple-solution", "baz", "other-tag"],
|
||||||
gonitoMetadataGeneralParams = M.empty,
|
gonitoMetadataGeneralParams = M.empty,
|
||||||
gonitoMetadataExternalLinks = []
|
gonitoMetadataExternalLinks = [],
|
||||||
|
gonitoMetadataDependencies = []
|
||||||
}
|
}
|
||||||
it "with gonito.yaml" $ do
|
it "with gonito.yaml" $ do
|
||||||
extractMetadataFromRepoDir "test/fake-git-repos/with-gonito-yaml/" def `shouldReturn` GonitoMetadata {
|
extractMetadataFromRepoDir "test/fake-git-repos/with-gonito-yaml/" def `shouldReturn` GonitoMetadata {
|
||||||
@ -41,5 +45,9 @@ spec = do
|
|||||||
gonitoMetadataExternalLinks = [
|
gonitoMetadataExternalLinks = [
|
||||||
Link (Just "gitlab") "https://about.gitlab.com/",
|
Link (Just "gitlab") "https://about.gitlab.com/",
|
||||||
Link (Just "Polish Wikipedia") "https://pl.wikipedia.org/wiki/Wikipedia:Strona_g%C5%82%C3%B3wna",
|
Link (Just "Polish Wikipedia") "https://pl.wikipedia.org/wiki/Wikipedia:Strona_g%C5%82%C3%B3wna",
|
||||||
Link Nothing "https://tvtropes.org/" ]
|
Link Nothing "https://tvtropes.org/" ],
|
||||||
|
gonitoMetadataDependencies = [
|
||||||
|
fromTextToSHA1 "39ae80911874c8f6bac1cdc57771bc2929cf0177",
|
||||||
|
fromTextToSHA1 "11b33fd677825228412019b289c470260389bea5"
|
||||||
|
]
|
||||||
}
|
}
|
||||||
|
@ -1 +1 @@
|
|||||||
Subproject commit 94553a6200cc5e89c195f92a75ae9724694797d1
|
Subproject commit 9addf5b00a9f917225934abca20b21f964e6fe92
|
Loading…
Reference in New Issue
Block a user