summaryrefslogtreecommitdiff
path: root/src/Config.hs
blob: 68db57d5b1322808f4acc194ba68cc54d06e70db (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
module Config (
    Config(..),
    findConfig,
    parseConfig,

    loadConfigForCommit,
    loadJobSetForCommit,
) where

import Control.Monad
import Control.Monad.Combinators
import Control.Monad.IO.Class

import Data.ByteString.Lazy qualified as BS
import Data.Either
import Data.List
import Data.Map qualified as M
import Data.Maybe
import Data.Ord
import Data.Text (Text)
import Data.Text qualified as T
import Data.YAML

import System.Directory
import System.FilePath
import System.Process

import Job.Types
import Repo


configFileName :: FilePath
configFileName = "minici.yaml"


data Config = Config
    { configJobs :: [ DeclaredJob ]
    , configRepos :: [ DeclaredRepo ]
    }

instance Semigroup Config where
    a <> b = Config
        { configJobs = configJobs a ++ configJobs b
        , configRepos = configRepos a ++ configRepos b
        }

instance Monoid Config where
    mempty = Config
        { configJobs = []
        , configRepos = []
        }

instance FromYAML Config where
    parseYAML = withMap "Config" $ \m -> do
        let getpos = \case (Scalar pos _, _) -> pos
                           (Mapping pos _ _, _) -> pos
                           (Sequence pos _ _, _) -> pos
                           (Anchor pos _ _, _) -> pos
        foldM go mempty $ sortBy (comparing $ posLine . getpos) $ M.assocs m
      where
        go config = \case
            (Scalar _ (SStr tag), node)
                | [ "job", name ] <- T.words tag -> do
                    job <- parseJob name node
                    return $ config { configJobs = configJobs config ++ [ job ] }
                | [ "repo", name ] <- T.words tag -> do
                    repo <- parseRepo name node
                    return $ config { configRepos = configRepos config ++ [ repo ] }
            _ -> return config

parseJob :: Text -> Node Pos -> Parser DeclaredJob
parseJob name node = flip (withMap "Job") node $ \j -> do
    let jobName = JobName name
    ( jobContainingCheckout, jobOtherCheckout ) <- partitionEithers <$> choice
        [ parseSingleCheckout =<< j .: "checkout"
        , parseMultipleCheckouts =<< j .: "checkout"
        , withNull "no checkout" (return []) =<< j .: "checkout"
        , return [ Left $ JobCheckout Nothing Nothing ]
        ]
    jobRecipe <- choice
        [ cabalJob =<< j .: "cabal"
        , shellJob =<< j .: "shell"
        ]
    jobArtifacts <- parseArtifacts j
    jobUses <- maybe (return []) parseUses =<< j .:? "uses"
    return Job {..}

parseSingleCheckout :: Node Pos -> Parser [ Either JobCheckout ( JobRepo Declared, JobCheckout ) ]
parseSingleCheckout = withMap "checkout definition" $ \m -> do
    mbName <- m .:? "repo"
    jcSubtree <- fmap T.unpack <$> m .:? "subtree"
    jcDestination <- fmap T.unpack <$> m .:? "dest"
    let checkout = JobCheckout {..}
    return $ (: []) $ case mbName of
        Nothing -> Left checkout
        Just name -> Right ( DeclaredJobRepo (RepoName name), checkout )

parseMultipleCheckouts :: Node Pos -> Parser [ Either JobCheckout ( JobRepo Declared, JobCheckout ) ]
parseMultipleCheckouts = withSeq "checkout definitions" $ fmap concat . mapM parseSingleCheckout

cabalJob :: Node Pos -> Parser [CreateProcess]
cabalJob = withMap "cabal job" $ \m -> do
    ghcOptions <- m .:? "ghc-options" >>= \case
        Nothing -> return []
        Just s -> withSeq "GHC option list" (mapM (withStr "GHC option" return)) s

    return
        [ proc "cabal" $ concat [ ["build"], ("--ghc-option="++) . T.unpack <$> ghcOptions ] ]

shellJob :: Node Pos -> Parser [CreateProcess]
shellJob = withSeq "shell commands" $ \xs -> do
    fmap (map shell) $ forM xs $ withStr "shell command" $ return . T.unpack

parseArtifacts :: Mapping Pos -> Parser [(ArtifactName, CreateProcess)]
parseArtifacts m = do
    fmap catMaybes $ forM (M.assocs m) $ \case
        (Scalar _ (SStr tag), node) | ["artifact", name] <- T.words tag -> do
            Just <$> parseArtifact name node
        _ -> return Nothing
  where
    parseArtifact name = withMap "Artifact" $ \am -> do
        path <- am .: "path"
        return (ArtifactName name, proc "echo" [ T.unpack path ])

parseUses :: Node Pos -> Parser [(JobName, ArtifactName)]
parseUses = withSeq "Uses list" $ mapM $
    withStr "Artifact reference" $ \text -> do
        [job, art] <- return $ T.split (== '.') text
        return (JobName job, ArtifactName art)


parseRepo :: Text -> Node Pos -> Parser DeclaredRepo
parseRepo name node = flip (withMap "Repo") node $ \r -> DeclaredRepo
    <$> pure (RepoName name)
    <*> (T.unpack <$> r .: "path")


findConfig :: IO (Maybe FilePath)
findConfig = go "."
  where
    go path = do
        doesFileExist (path </> configFileName) >>= \case
            True -> return $ Just $ path </> configFileName
            False -> doesDirectoryExist (path </> "..") >>= \case
                True -> do
                    parent <- canonicalizePath $ path </> ".."
                    if parent /= path then go parent
                                      else return Nothing
                False -> return Nothing

parseConfig :: BS.ByteString -> Either String Config
parseConfig contents = do
    case decode1 contents of
        Left (pos, err) -> do
            Left $ prettyPosWithSource pos contents err
        Right conf -> Right conf

loadConfigForCommit :: MonadIO m => Commit -> m (Either String Config)
loadConfigForCommit commit = do
    readCommittedFile commit configFileName >>= return . \case
        Just content -> either (\_ -> Left $ "failed to parse " <> configFileName) Right $ parseConfig content
        Nothing -> Left $ configFileName <> " not found"

loadJobSetForCommit :: MonadIO m => Commit -> m DeclaredJobSet
loadJobSetForCommit commit = toJobSet <$> loadConfigForCommit commit
  where
    toJobSet configEither = JobSet
        { jobsetCommit = Just commit
        , jobsetJobsEither = fmap configJobs configEither
        }