Skip to content

Commit

Permalink
curator CLI
Browse files Browse the repository at this point in the history
  • Loading branch information
bergmark committed Aug 18, 2018
1 parent 1a98bff commit e16cdaa
Show file tree
Hide file tree
Showing 2 changed files with 74 additions and 42 deletions.
115 changes: 73 additions & 42 deletions subs/curator/app/Main.hs
Original file line number Diff line number Diff line change
@@ -1,52 +1,83 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
import Curator
{-# LANGUAGE TypeOperators #-}
import Curator hiding (updateHackageIndex, Snapshot)
import Data.Yaml (encodeFile, decodeFileThrow)
import Options.Generic (ParseRecord, getRecord)
import Path.IO (resolveFile', resolveDir')
import RIO.Process
import qualified Curator

data CuratorOptions
= Update
| Constraints
| SnapshotIncomplete
| Snapshot
| Unpack
| Build
deriving (Eq, Show, Generic)

instance ParseRecord CuratorOptions

main :: IO ()
main = runPantryApp $ do
-- each of these should be separate commands

-- update Hackage index
do
void $ updateHackageIndex $ Just "Running snapshot curator tool"

-- write constraints
do
logInfo "Writing constraints.yaml"
loadStackageConstraints "build-constraints.yaml" >>= liftIO . encodeFile "constraints.yaml"

-- create snapshot
do
logInfo "Writing snapshot-incomplete.yaml"
decodeFileThrow "constraints.yaml" >>= \constraints ->
makeSnapshot constraints "my-test-snapshot" >>=
liftIO . encodeFile "snapshot-incomplete.yaml"

-- complete snapshot
do
logInfo "Writing snapshot.yaml"
incomplete <- loadPantrySnapshotFile "snapshot-incomplete.yaml"
complete <- completeSnapshot incomplete
liftIO $ encodeFile "snapshot.yaml" complete

do
logInfo "Unpacking files"
snapshot <- loadPantrySnapshotFile "snapshot.yaml"
constraints <- decodeFileThrow "constraints.yaml"
dest <- resolveDir' "unpack-dir"
unpackSnapshot constraints snapshot dest

do
logInfo "Building"
withWorkingDir "unpack-dir" $ proc
"stack"
(words "build --test --bench --no-rerun-tests --no-run-benchmarks --haddock")
runProcess_

loadPantrySnapshotFile :: FilePath -> RIO PantryApp Snapshot
main = runPantryApp $
getRecord "curator" >>= \case
Update ->
updateHackageIndex
Constraints ->
constraints
SnapshotIncomplete ->
snapshotIncomplete
Snapshot ->
snapshot
Unpack ->
unpackFiles
Build ->
build

updateHackageIndex :: RIO PantryApp ()
updateHackageIndex = do
void $ Curator.updateHackageIndex $ Just "Updating hackage index"

constraints :: RIO PantryApp ()
constraints = do
logInfo "Writing constraints.yaml"
loadStackageConstraints "build-constraints.yaml" >>= liftIO . encodeFile "constraints.yaml"

snapshotIncomplete :: RIO PantryApp ()
snapshotIncomplete = do
logInfo "Writing snapshot-incomplete.yaml"
decodeFileThrow "constraints.yaml" >>= \constraints ->
makeSnapshot constraints "my-test-snapshot-2" >>=
liftIO . encodeFile "snapshot-incomplete.yaml"

snapshot :: RIO PantryApp ()
snapshot = do
logInfo "Writing snapshot.yaml"
incomplete <- loadPantrySnapshotFile "snapshot-incomplete.yaml"
complete <- completeSnapshot incomplete
liftIO $ encodeFile "snapshot.yaml" complete

unpackFiles :: RIO PantryApp ()
unpackFiles = do
logInfo "Unpacking files"
snapshot <- loadPantrySnapshotFile "snapshot.yaml"
constraints <- decodeFileThrow "constraints.yaml"
dest <- resolveDir' "unpack-dir"
unpackSnapshot constraints snapshot dest

build :: RIO PantryApp ()
build = do
logInfo "Building"
withWorkingDir "unpack-dir" $ proc
"stack"
(words "build --test --bench --no-rerun-tests --no-run-benchmarks --haddock")
runProcess_

loadPantrySnapshotFile :: FilePath -> RIO PantryApp Curator.Snapshot
loadPantrySnapshotFile fp = do
abs' <- resolveFile' fp
eres <- loadPantrySnapshot $ SLFilePath (ResolvedPath (RelFilePath (fromString fp)) abs') Nothing
Expand Down
1 change: 1 addition & 0 deletions subs/curator/package.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,7 @@ dependencies:
- yaml
- path
- path-io
- optparse-generic

library:
source-dirs: src
Expand Down

0 comments on commit e16cdaa

Please sign in to comment.