This commit is contained in:
Yann Esposito (Yogsototh) 2018-10-21 11:28:22 +02:00
parent 8a2783470d
commit a79af4e822
Signed by untrusted user who does not match committer: yogsototh
GPG key ID: 7B19A4C650D59646
3 changed files with 28 additions and 17 deletions

View file

@ -9,7 +9,7 @@ Maintainer : yann.esposito@gmail.com
module GPM module GPM
where where
import Protolude hiding (stdout) import Protolude
import Turtle import Turtle

View file

@ -20,18 +20,24 @@ module GPM.Helpers
) )
where where
import Protolude hiding (die) import Protolude hiding (die)
import Turtle import Turtle
import qualified Control.Foldl as Fold import qualified Control.Foldl as Fold
import qualified System.Directory as Directory
import qualified System.Console.ANSI as Console import qualified System.Console.ANSI as Console
import qualified System.Directory as Directory
import qualified System.IO
-- | execute a shell script and return the last line as text -- | execute a shell script and return the last line as text
-- but also log the command to the console to minimize surprise -- but also log the command to the console to minimize surprise
debug :: Text -> IO (Maybe Text) debug :: Text -> IO (Maybe Text)
debug cmd = do debug cmd = do
putErrText cmd Console.setSGR [ Console.SetColor Console.Foreground Console.Dull Console.Cyan
, Console.SetItalicized True
]
putErrText (" " <> cmd)
Console.setSGR [ Console.Reset ]
System.IO.hFlush System.IO.stderr
fmap lineToText <$> _foldIO (inshell cmd empty) (Fold.generalize Fold.last) fmap lineToText <$> _foldIO (inshell cmd empty) (Fold.generalize Fold.last)
-- | execute a shell script without stdin and without handling output -- | execute a shell script without stdin and without handling output
@ -78,11 +84,10 @@ inDir workDir action = do
putTextColor :: Console.Color -> Text -> IO () putTextColor :: Console.Color -> Text -> IO ()
putTextColor color t = do putTextColor color t = do
Console.setSGR [ Console.SetColor Console.Foreground Console.Dull color Console.setSGR [ Console.SetColor Console.Foreground Console.Dull color ]
, Console.SetConsoleIntensity Console.NormalIntensity
]
putText t putText t
Console.setSGR [Console.Reset] Console.setSGR [ Console.Reset ]
System.IO.hFlush System.IO.stdout
green :: Text -> IO () green :: Text -> IO ()
green = putTextColor Console.Green green = putTextColor Console.Green

View file

@ -43,15 +43,21 @@ data ReviewCommand = ReviewStart ReviewOptions
-- | init gpm branch to handle reviews -- | init gpm branch to handle reviews
init :: IO () init :: IO ()
init = do init = do
green "* Init Reviews support" green "* reviews.org"
let fic = "reviews" </> "write-contributing-yogsototh.org" putText " create some example review for inspiration"
mktree "reviews" let reviewDir = "reviews"
putText $ format ("* "%fp) fic mktree reviewDir
let fic = reviewDir </> "write-contributing-yogsototh.org"
putText $ format (" "%fp) fic
writeFile (toS (format fp fic)) $(embedStringFile "templates/review.org") writeFile (toS (format fp fic)) $(embedStringFile "templates/review.org")
debug_ "git add reviews" debug_ (toS (format ("git add "%fp) reviewDir))
mktree "templates" putText " create some review templates"
writeFile "templates/new-review.org" $(embedStringFile "templates/new-review.org") let templateDir = "templates"
debug_ "git add templates" templateFic = templateDir </> "new-review.org"
mktree templateDir
writeFile (toS (format fp templateFic)) $(embedStringFile "templates/new-review.org")
putText $ format (" "%fp) templateFic
debug_ (toS (format ("git add "%fp) templateDir))
-- | Command Line Options -- | Command Line Options
data ReviewOptions = ReviewOptions data ReviewOptions = ReviewOptions