diff --git a/bin/changelog.hs b/bin/changelog.hs index a83252dfb..2466dba3f 100755 --- a/bin/changelog.hs +++ b/bin/changelog.hs @@ -14,6 +14,15 @@ -- Manipulate a hledger changelog. Currently does one thing: prompts -- for a rewrite of the oldest uncategorised pending changelog item -- and updates the file, printing a diff. +-- +-- My workflow: +-- - In a terminal window (not emacs shell, it will hang) run this on a CHANGES.md file +-- - Edit the changelog item to changelog-readiness (if needed) +-- - Save and quit (C-x #) to do the next; it will exit after the last. Or C-x C-x to stop. +-- - On the side keep an auto-reverting editor open on the file to watch progress or for fixups. +-- It might seem a bit pointless, but it made this old chore much more +-- pleasant. I can do just one, or more as I feel it, and my attention +-- is not dragged on by pending items. {-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE DeriveGeneric #-} @@ -26,19 +35,12 @@ import GHC.Generics import Data.List.Extra import qualified Data.Text as T import System.Environment -import System.IO +import System.IO.Extra +-- import System.IO import System.Process import Text.Printf import Hledger.Utils --- The one-line heading for a top level section in the changelog, --- with the leading #(s) removed. -type ChangelogHeading = String - --- One change description in the changelog, with the list bullet and --- corresponding indentation removed. -type ChangelogItem = String - -- A top level section in the changelog, corresponding to one release. data ChangelogSection = ChangelogSection { heading :: ChangelogHeading @@ -47,46 +49,70 @@ data ChangelogSection = ChangelogSection { ,improvementitems :: [ChangelogItem] ,fixitems :: [ChangelogItem] } - deriving (Show, Generic, Default) + deriving (Show, Eq, Generic, Default) + +-- The one-line heading for a top level section in the changelog, +-- with the leading #(s) removed. +type ChangelogHeading = String + +-- One change description in the changelog, with the list bullet and +-- corresponding indentation removed. +type ChangelogItem = String main = do - (i:_) <- getArgs + (f:_) <- getArgs + go f +go f = do -- read specified changelog - (preamble:first:rest) <- splitOn "\n# " <$> readFile i + (preamble:first:rest) <- splitOn "\n# " <$> readFile f let - o = i ++ ".new" + g = f ++ ".new" s@ChangelogSection{..} = readSection first + + -- ask for an edit of this item's text s' <- editOneUnknown s - -- write back to new file - writeFile o $ init $ unlines $ - preamble : - showSection s' : - map ("# "++) rest - - -- show the diff - system' $ printf "diff %s %s" i o - - -- overwrite the old file - system' $ printf "mv %s %s" o i + if s' == s + then return () -- if it's unchanged, quit + else do + -- otherwise write to a temp file + writeFile g $ init $ unlines $ + preamble : + showSection s' : + map ("# "++) rest + -- and show the diff + system' $ printf "diff %s %s" f g + -- and replace the old file + system' $ printf "mv %s %s" g f + -- and repeat + go f editOneUnknown :: ChangelogSection -> IO ChangelogSection editOneUnknown s@ChangelogSection{..} | null unknownitems = return s | otherwise = do - let u = last unknownitems - putStrLn "Old:\n" - putStrLn u - putStrLn "New: (prefix with feat:/imp:/fix: to categorise, ctrl-d to finish):\n" -- Just an = keeps it unchanged, empty string removes it.\n" - i <- getContents - let s' = - case i of - 'f':'e':'a':'t':':':' ':t -> s{featureitems = readItem t : featureitems} - 'f':'i':'x':':':' ':t -> s{fixitems = readItem t : fixitems} - 'i':'m':'p':':':' ':t -> s{improvementitems = readItem t : improvementitems} - t -> s{improvementitems = readItem t : improvementitems} - return s'{unknownitems=init unknownitems} + let + s' = s{unknownitems=init unknownitems} + u = last unknownitems + new <- textEditEditor u + return $ case new of + 'f':'e':'a':'t':':':' ':t -> s'{featureitems = readItem t : featureitems} + 'f':'i':'x':':':' ':t -> s'{fixitems = readItem t : fixitems} + 'i':'m':'p':':':' ':t -> s'{improvementitems = readItem t : improvementitems} + t -> s'{improvementitems = readItem t : improvementitems} + +textEditEditor t = withTempFile $ \f -> do + writeFile f t + ed <- getEnv "EDITOR" + system $ printf "%s %s" ed f + readFile f + +-- textEditTty u = do +-- putStrLn "Old:" +-- putStrLn u +-- putStrLn "New: (prefix with feat:/imp:/fix: to categorise, ctrl-d to finish):\n" -- Just an = keeps it unchanged, empty string removes it." +-- getContents -- Parse a changelog section which may or may not have the Features/Improvements/Fixes subheadings. readSection :: String -> ChangelogSection