Change HashMap to Map, clean up
This commit is contained in:
parent
1ff7c34714
commit
d3e2c06b15
@ -22,7 +22,7 @@ import System.Exit
|
|||||||
import System.Process
|
import System.Process
|
||||||
|
|
||||||
import qualified Data.Set as S
|
import qualified Data.Set as S
|
||||||
import qualified Data.HashMap.Strict as H
|
import qualified Data.Map.Strict as M
|
||||||
|
|
||||||
import Handler.Shared (gitPath)
|
import Handler.Shared (gitPath)
|
||||||
|
|
||||||
@ -31,7 +31,7 @@ import "Glob" System.FilePath.Glob as G
|
|||||||
data ExtractionOptions = ExtractionOptions {
|
data ExtractionOptions = ExtractionOptions {
|
||||||
extractionOptionsDescription :: Maybe Text,
|
extractionOptionsDescription :: Maybe Text,
|
||||||
extractionOptionsTags :: Maybe Text,
|
extractionOptionsTags :: Maybe Text,
|
||||||
extractionOptionsGeneralParams :: Maybe (H.HashMap Text Text),
|
extractionOptionsGeneralParams :: Maybe (M.Map Text Text),
|
||||||
extractionOptionsUnwantedParams :: Maybe [Text],
|
extractionOptionsUnwantedParams :: Maybe [Text],
|
||||||
extractionOptionsParamFiles :: Maybe [String],
|
extractionOptionsParamFiles :: Maybe [String],
|
||||||
extractionOptionsMLRunPath :: Maybe FilePath
|
extractionOptionsMLRunPath :: Maybe FilePath
|
||||||
@ -59,7 +59,7 @@ instance Default ExtractionOptions where
|
|||||||
data GonitoMetadata = GonitoMetadata {
|
data GonitoMetadata = GonitoMetadata {
|
||||||
gonitoMetadataDescription :: Text,
|
gonitoMetadataDescription :: Text,
|
||||||
gonitoMetadataTags :: S.Set Text,
|
gonitoMetadataTags :: S.Set Text,
|
||||||
gonitoMetadataGeneralParams :: H.HashMap Text Text
|
gonitoMetadataGeneralParams :: M.Map Text Text
|
||||||
}
|
}
|
||||||
deriving (Eq, Show)
|
deriving (Eq, Show)
|
||||||
|
|
||||||
@ -75,9 +75,9 @@ combineExtractionOptions Nothing options = options
|
|||||||
combineExtractionOptions (Just otherOptions) options = ExtractionOptions {
|
combineExtractionOptions (Just otherOptions) options = ExtractionOptions {
|
||||||
extractionOptionsDescription = combineWithT extractionOptionsDescription,
|
extractionOptionsDescription = combineWithT extractionOptionsDescription,
|
||||||
extractionOptionsTags = combineWithT extractionOptionsTags,
|
extractionOptionsTags = combineWithT extractionOptionsTags,
|
||||||
extractionOptionsGeneralParams = Just $ (fromMaybe H.empty $ extractionOptionsGeneralParams options)
|
extractionOptionsGeneralParams = Just $ (fromMaybe M.empty $ extractionOptionsGeneralParams options)
|
||||||
`H.union`
|
`M.union`
|
||||||
(fromMaybe H.empty $ extractionOptionsGeneralParams otherOptions),
|
(fromMaybe M.empty $ extractionOptionsGeneralParams otherOptions),
|
||||||
extractionOptionsUnwantedParams = Just $ (fromMaybe [] $ extractionOptionsUnwantedParams options)
|
extractionOptionsUnwantedParams = Just $ (fromMaybe [] $ extractionOptionsUnwantedParams options)
|
||||||
++
|
++
|
||||||
(fromMaybe [] $ extractionOptionsUnwantedParams otherOptions),
|
(fromMaybe [] $ extractionOptionsUnwantedParams otherOptions),
|
||||||
@ -112,17 +112,16 @@ extractMetadataFromRepoDir repoDir formExtractionOptions = do
|
|||||||
let tagsParsed = union commitTagsParsed formTagsParsed
|
let tagsParsed = union commitTagsParsed formTagsParsed
|
||||||
|
|
||||||
paramFiles <- case extractionOptionsParamFiles extractionOptions of
|
paramFiles <- case extractionOptionsParamFiles extractionOptions of
|
||||||
Just paramFilesGlobs -> G.globDir (Import.map G.compile $ traceShowId paramFilesGlobs) repoDir
|
Just paramFilesGlobs -> G.globDir (Import.map G.compile paramFilesGlobs) repoDir
|
||||||
Nothing -> pure []
|
Nothing -> pure []
|
||||||
|
|
||||||
params' <- H.unions <$> (mapM parseParamFile
|
params' <- M.unions <$> (mapM parseParamFile
|
||||||
$ traceShowId
|
|
||||||
$ Import.filter (/= (repoDir </> gonitoYamlFile))
|
$ Import.filter (/= (repoDir </> gonitoYamlFile))
|
||||||
$ Import.concat paramFiles)
|
$ Import.concat paramFiles)
|
||||||
let params =
|
let params =
|
||||||
Import.foldl' (flip H.delete) params' (fromMaybe [] $ extractionOptionsUnwantedParams extractionOptions)
|
Import.foldl' (flip M.delete) params' (fromMaybe [] $ extractionOptionsUnwantedParams extractionOptions)
|
||||||
`H.union`
|
`M.union`
|
||||||
fromMaybe H.empty (extractionOptionsGeneralParams extractionOptions)
|
fromMaybe M.empty (extractionOptionsGeneralParams extractionOptions)
|
||||||
|
|
||||||
pure $ GonitoMetadata {
|
pure $ GonitoMetadata {
|
||||||
gonitoMetadataDescription = description,
|
gonitoMetadataDescription = description,
|
||||||
@ -131,18 +130,18 @@ extractMetadataFromRepoDir repoDir formExtractionOptions = do
|
|||||||
}
|
}
|
||||||
|
|
||||||
|
|
||||||
parseParamFile :: FilePath -> IO (H.HashMap Text Text)
|
parseParamFile :: FilePath -> IO (M.Map Text Text)
|
||||||
parseParamFile yamlFile = do
|
parseParamFile yamlFile = do
|
||||||
decoded <- Y.decodeFileEither yamlFile
|
decoded <- Y.decodeFileEither yamlFile
|
||||||
|
|
||||||
return $ case decoded of
|
return $ case decoded of
|
||||||
Left _ -> H.empty
|
Left _ -> M.empty
|
||||||
Right h -> enforceTextHash h
|
Right h -> enforceTextHash h
|
||||||
|
|
||||||
enforceTextHash :: H.HashMap Text Value -> H.HashMap Text Text
|
enforceTextHash :: M.Map Text Value -> M.Map Text Text
|
||||||
enforceTextHash h = H.fromList
|
enforceTextHash h = M.fromList
|
||||||
$ Import.map (\(p, pv) -> (p, strip $ DTE.decodeUtf8 $ Y.encode pv))
|
$ Import.map (\(p, pv) -> (p, strip $ DTE.decodeUtf8 $ Y.encode pv))
|
||||||
$ H.toList h
|
$ M.toList h
|
||||||
|
|
||||||
getLastCommitMessage :: FilePath -> IO (Maybe Text)
|
getLastCommitMessage :: FilePath -> IO (Maybe Text)
|
||||||
getLastCommitMessage repoDir = do
|
getLastCommitMessage repoDir = do
|
||||||
|
@ -333,7 +333,7 @@ outsForTest repoDir submissionId testEnt@(Entity _ test) = do
|
|||||||
outFiles <- liftIO $ outFilesForTest repoDir test
|
outFiles <- liftIO $ outFilesForTest repoDir test
|
||||||
|
|
||||||
forM outFiles $ \outFile -> do
|
forM outFiles $ \outFile -> do
|
||||||
theVariant <- getVariant submissionId outFile
|
theVariant <- getVariant submissionId M.empty outFile
|
||||||
outForTest repoDir outFile theVariant testEnt
|
outForTest repoDir outFile theVariant testEnt
|
||||||
|
|
||||||
-- returns the filename (not file path)
|
-- returns the filename (not file path)
|
||||||
@ -348,8 +348,8 @@ outFilesForTest repoDir test = do
|
|||||||
Just outF -> return [takeFileName outF]
|
Just outF -> return [takeFileName outF]
|
||||||
Nothing -> return []
|
Nothing -> return []
|
||||||
|
|
||||||
getVariant :: SubmissionId -> FilePath -> Handler VariantId
|
getVariant :: SubmissionId -> M.Map Text Text -> FilePath -> Handler VariantId
|
||||||
getVariant submissionId outFilePath = runDB $ do
|
getVariant submissionId generalParams outFilePath = runDB $ do
|
||||||
let outFile = takeFileName outFilePath
|
let outFile = takeFileName outFilePath
|
||||||
let name = Data.Text.pack $ dropExtensions outFile
|
let name = Data.Text.pack $ dropExtensions outFile
|
||||||
maybeVariant <- getBy $ UniqueVariantSubmissionName submissionId name
|
maybeVariant <- getBy $ UniqueVariantSubmissionName submissionId name
|
||||||
@ -358,9 +358,11 @@ getVariant submissionId outFilePath = runDB $ do
|
|||||||
Nothing -> do
|
Nothing -> do
|
||||||
vid <- insert $ Variant submissionId name
|
vid <- insert $ Variant submissionId name
|
||||||
let (OutputFileParsed _ paramMap) = parseParamsFromFilePath outFile
|
let (OutputFileParsed _ paramMap) = parseParamsFromFilePath outFile
|
||||||
forM_ (M.toList paramMap) $ \(param, val) -> do
|
|
||||||
|
forM_ (M.toList (paramMap `M.union` generalParams)) $ \(param, val) -> do
|
||||||
_ <- insert $ Parameter vid param val
|
_ <- insert $ Parameter vid param val
|
||||||
return ()
|
return ()
|
||||||
|
|
||||||
return vid
|
return vid
|
||||||
|
|
||||||
checkOrInsertOut :: Out -> Handler ()
|
checkOrInsertOut :: Out -> Handler ()
|
||||||
|
@ -5,7 +5,7 @@ module Gonito.ExtractMetadataSpec (spec) where
|
|||||||
import Import
|
import Import
|
||||||
|
|
||||||
import qualified Data.Set as S
|
import qualified Data.Set as S
|
||||||
import qualified Data.HashMap.Strict as H
|
import qualified Data.Map.Strict as M
|
||||||
|
|
||||||
import Test.Hspec
|
import Test.Hspec
|
||||||
import Gonito.ExtractMetadata (extractMetadataFromRepoDir, GonitoMetadata(..), ExtractionOptions(..))
|
import Gonito.ExtractMetadata (extractMetadataFromRepoDir, GonitoMetadata(..), ExtractionOptions(..))
|
||||||
@ -17,7 +17,7 @@ spec = do
|
|||||||
extractMetadataFromRepoDir "test/fake-git-repos/simple/" def `shouldReturn` GonitoMetadata {
|
extractMetadataFromRepoDir "test/fake-git-repos/simple/" def `shouldReturn` GonitoMetadata {
|
||||||
gonitoMetadataDescription = "Simple solution",
|
gonitoMetadataDescription = "Simple solution",
|
||||||
gonitoMetadataTags = S.fromList ["foo", "simple-solution", "baz"],
|
gonitoMetadataTags = S.fromList ["foo", "simple-solution", "baz"],
|
||||||
gonitoMetadataGeneralParams = H.empty
|
gonitoMetadataGeneralParams = M.empty
|
||||||
}
|
}
|
||||||
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 {
|
||||||
@ -26,13 +26,13 @@ spec = do
|
|||||||
} `shouldReturn` GonitoMetadata {
|
} `shouldReturn` GonitoMetadata {
|
||||||
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 = H.empty
|
gonitoMetadataGeneralParams = M.empty
|
||||||
}
|
}
|
||||||
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 {
|
||||||
gonitoMetadataDescription = "Test solution",
|
gonitoMetadataDescription = "Test solution",
|
||||||
gonitoMetadataTags = S.fromList ["zzz", "baz", "simple", "machine-learning"],
|
gonitoMetadataTags = S.fromList ["zzz", "baz", "simple", "machine-learning"],
|
||||||
gonitoMetadataGeneralParams = H.fromList [("level", "4"),
|
gonitoMetadataGeneralParams = M.fromList [("level", "4"),
|
||||||
("altitude", "8900.3"),
|
("altitude", "8900.3"),
|
||||||
("q", "10.4"),
|
("q", "10.4"),
|
||||||
("style", "bold")]
|
("style", "bold")]
|
||||||
|
@ -1 +1 @@
|
|||||||
Subproject commit e54aa938430ccf03383d84a435183aa8d8f64a8b
|
Subproject commit a71de45eacb63081b2b39db09c48ad3d848c2541
|
Loading…
Reference in New Issue
Block a user