{-# LANGUAGE OverloadedStrings #-}
module FeedGipeda.Gipeda
( GipedaSettings (..)
, BenchmarkSettings (..)
, settingsForRepo
, determineBenchmarkScript
) where
import Control.Applicative
import qualified Control.Logging as Logging
import Control.Monad (liftM2, when)
import Data.Aeson (withArray, withObject)
import Data.Either (either)
import Data.Functor
import Data.Maybe (catMaybes, fromMaybe, isJust, isNothing)
import Data.String (fromString)
import qualified Data.Text as Text
import Data.Yaml (FromJSON (..), ToJSON (..), (.:), (.=))
import qualified Data.Yaml as Yaml
import FeedGipeda.GitShell (SHA)
import qualified FeedGipeda.GitShell as GitShell
import FeedGipeda.Prelude
import FeedGipeda.Repo (Repo)
import qualified FeedGipeda.Repo as Repo
import System.Directory (doesFileExist)
import Text.Printf (printf)
data GipedaSettings = GipedaSettings
{ title :: String
, revisionInfo :: String
, diffLink :: String
, limitRecent :: Int
, start :: Maybe SHA
, interestingTags :: String
, interestingBranches :: String
, benchmarkScript :: String
, benchmarks :: [BenchmarkSettings]
} deriving (Show)
data BenchmarkSettings = BenchmarkSettings
{ match :: String
, smallerIsBetter :: Maybe Bool
, unit :: Maybe String
, type_ :: Maybe String
, group :: Maybe String
, threshold :: Maybe Double
, important :: Maybe Bool
} deriving (Show)
benchmark :: String -> BenchmarkSettings
benchmark match = BenchmarkSettings
{ match = match
, smallerIsBetter = Nothing
, unit = Nothing
, type_ = Nothing
, group = Nothing
, threshold = Nothing
, important = Nothing
}
instance ToJSON BenchmarkSettings where
toJSON s = (Yaml.object . catMaybes)
[ "match" .=? Just (match s)
, "smallerIsBetter" .=? smallerIsBetter s
, "unit" .=? unit s
, "type" .=? type_ s
, "group" .=? group s
, "threshold" .=? threshold s
, "important" .=? important s
] where key .=? value = fmap (key .=) value
instance FromJSON BenchmarkSettings where
parseJSON (Yaml.Object o) = BenchmarkSettings
<$> o .: "match"
<*> o .? "smallerIsBetter"
<*> o .? "unit"
<*> o .? "type"
<*> o .? "group"
<*> o .? "threshold"
<*> o .? "important"
where o .? key = optional (o .: key)
instance ToJSON GipedaSettings where
toJSON s = Yaml.object
[ "title" .= title s
, "revisionInfo" .= revisionInfo s
, "diffLink" .= diffLink s
, "limitRecent" .= limitRecent s
, "start" .= start s
, "interestingTags" .= interestingTags s
, "interestingBranches" .= interestingBranches s
, "benchmarkScript" .= benchmarkScript s
, "benchmarks" .= benchmarks s
]
determineBenchmarkScript :: Repo -> IO String
determineBenchmarkScript repo = do
settingsFile <- Repo.settingsFile repo
exists <- doesFileExist settingsFile
maybeSettings <- if exists then Yaml.decodeFile settingsFile else return Nothing
return $ fromMaybe "cloben" $ do
(Yaml.Object settings) <- maybeSettings
Yaml.parseMaybe (\_ -> settings .: "benchmarkScript") ()
settingsForRepo :: Repo -> IO GipedaSettings
settingsForRepo repo = do
let a <?> b = liftM2 (<|>) a b
clone <- Repo.cloneDir repo
firstCommit <- GitShell.firstCommit clone
gipedaYaml <-
GitShell.showHead clone ".gipeda.yaml"
<?> GitShell.showHead clone ".gipeda.yml"
<?> GitShell.showHead clone "gipeda.yaml"
<?> GitShell.showHead clone "gipeda.yml"
<?> (Repo.settingsFile repo >>= readFileMaybe)
let
parsedValue :: Either String Yaml.Value
parsedValue = do
contents <- maybe (Left "Could not find a gipeda.yaml.") Right gipedaYaml
either (Left . ("Could not parse the supplied gipeda.yaml:\n" ++)) Right $
Yaml.decodeEither (fromString contents)
revisionInfo :: String
revisionInfo =
printf "<a href=\"%s/commit/{{rev}}>View Diff</a>" (Repo.uri repo)
settings :: Yaml.Value -> Yaml.Parser GipedaSettings
settings (Yaml.Object obj) =
GipedaSettings
<$> "title" ?? Repo.shortName repo
<*> "revisionInfo" ?? printf "<a href=\"%s/commit/{{rev}}\">View Diff</a>" (Repo.uri repo)
<*> "diffLink" ?? printf "%s/compare/{{base}}...{{rev}}" (Repo.uri repo)
<*> "limitRecent" ?? 20
<*> ((Just <$> obj .: "start") <|> pure firstCommit)
<*> "interestingTags" ?? "*"
<*> "interestingBranches" ?? "*"
<*> "benchmarkScript" ?? "cloben"
<*> "benchmarks" ?? []
where key ?? def = obj .: key <|> pure def
settings _ = settings (Yaml.object [])
case parsedValue of
Left err -> do
logWarn err
Yaml.parseMonad settings (Yaml.object [])
Right value ->
Yaml.parseMonad settings value