This tool generates the cabal files for the regex and regex-examples packages as well as the cabal file for the development tree (contaiing the combined targets of both packages). In addition it contains scripts for bumping the version number and generating the Hackage releases.
The tool is self-testing: run it with no arguments (or cabal test
).
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE CPP #-}
module Main (main) where
import qualified Data.ByteString.Lazy.Char8 as LBS
import Data.Char
import Data.IORef
import qualified Data.List as L
import qualified Data.Map as Map
import Data.Maybe
import qualified Data.Monoid as M
import qualified Data.Text as T
import qualified Data.Text.Encoding as TE
import Prelude.Compat
import qualified Shelly as SH
import System.Directory
import System.Environment
import System.Exit
import System.IO
import TestKit
import Text.Printf
import Text.RE.Replace
import Text.RE.TDFA.ByteString.Lazy
import qualified Text.RE.TDFA.Text as T
import Text.RE.Tools.Grep
import Text.RE.Tools.Sed
main :: IO ()
= do
main <- (,) <$> getProgName <*> getArgs
(pn,as) case as of
-> test
[] "test"] -> test
["bump-version",vrn] -> bumpVersion vrn >> gen
["test-release",vrn] -> test_release $ T.pack vrn
["commit-message"] -> commit_message
["sdist"] -> sdist
["gen"] -> gen
[-> do
_ let prg = ((" "++pn++" ")++)
$ unlines
hPutStr stderr "usage:"
[ "--help"
, prg "[test]"
, prg "bump-version <version>"
, prg "test-release <version>"
, prg "commit-message"
, prg "sdist"
, prg "gen"
, prg
]$ ExitFailure 1
exitWith
test :: IO ()
= do
test False "tmp"
createDirectoryIfMissing "lib/cabal-masters/mega-regex.cabal" "tmp/mega-regex.cabal"
gen1 <- cmp "tmp/mega-regex.cabal" "lib/mega-regex.cabal"
ok case ok of
True -> return ()
False -> exitWith $ ExitFailure 1
gen :: IO ()
= do
gen "lib/cabal-masters/mega-regex.cabal" "lib/mega-regex.cabal"
gen1 "lib/cabal-masters/regex.cabal" "lib/regex.cabal"
gen1 "lib/cabal-masters/regex-with-pcre.cabal" "lib/regex-with-pcre.cabal"
gen1 "lib/cabal-masters/regex-examples.cabal" "lib/regex-examples.cabal"
gen1 "mega-regex" "regex"
establish
gen1 :: FilePath -> FilePath -> IO ()
= do
gen1 in_f out_f <- setup
ctx =<<
LBS.writeFile out_f =<< substVersion_ =<< include =<<
sed' (gc_script ctx)
LBS.readFile in_f
data Ctx =
Ctx
_ctx_w_error :: IORef Bool
{ _ctx_filter_pcre :: IORef Bool
, _ctx_package_constraints :: IORef (Map.Map LBS.ByteString LBS.ByteString)
, _ctx_test_exe :: IORef (Maybe TestExe)
,
}
data TestExe =
TestExe
_te_test :: Bool
{ _te_exe :: Bool
, _te_name :: LBS.ByteString
, _te_text :: LBS.ByteString
,
}deriving (Show)
setup :: IO Ctx
= Ctx <$> (newIORef True) <*> (newIORef False) <*> (newIORef Map.empty) <*> (newIORef Nothing)
setup
gc_script :: Ctx -> Edits IO RE LBS.ByteString
= Select
gc_script ctx LineEdit [re|^%Werror$|] $ w_error_gen ctx
[ LineEdit [re|^%Wwarn$|] $ w_warn_gen ctx
, LineEdit [re|^%filter-regex-with-pcre$|] $ w_filter_pcre ctx
, LineEdit [re|^%- +${pkg}(@{%id-}) +${cond}(.*)$|] $ cond_gen ctx
, LineEdit [re|^%build-depends-${lb}(lib|prog) +${list}(@{%id-}( +@{%id-})*)$|]
, $ build_depends_gen ctx
LineEdit [re|^%test +${i}(@{%id-})$|] $ test_exe_gen True False ctx
, LineEdit [re|^%exe +${i}(@{%id-})$|] $ test_exe_gen False True ctx
, LineEdit [re|^%test-exe +${i}(@{%id-})$|] $ test_exe_gen True True ctx
, LineEdit [re|^.*$|] $ default_gen ctx
,
]
w_error_gen, w_warn_gen, w_filter_pcre, cond_gen, build_depends_gen, default_gen :: Ctx
-> LineNo
-> Matches LBS.ByteString
-> IO (LineEdit LBS.ByteString)
Ctx{..} _ _ = writeIORef _ctx_w_error True >> return Delete
w_error_gen Ctx{..} _ _ = writeIORef _ctx_w_error False >> return Delete
w_warn_gen Ctx{..} _ _ = writeIORef _ctx_filter_pcre True >> return Delete
w_filter_pcre
Ctx{..} _ mtchs = do
cond_gen $ Map.insert pkg cond
modifyIORef _ctx_package_constraints return Delete
where
= captureText [cp|pkg|] mtch
pkg = captureText [cp|cond|] mtch
cond
= allMatches mtchs !! 0
mtch
@Ctx{..} _ mtchs = do
build_depends_gen ctx<- readIORef _ctx_w_error
we <- readIORef _ctx_filter_pcre
fp <- readIORef _ctx_package_constraints
mp $ mk_build_depends lb we fp mp lst
put ctx where
= captureText [cp|lb|] mtch == "lib"
lb = LBS.words $ captureText [cp|list|] mtch
lst = allMatches mtchs !! 0
mtch
@Ctx{..} _ mtchs = do
default_gen ctx<- readIORef _ctx_test_exe
mb case mb of
Nothing -> return $ ReplaceWith ln
Just te -> case isSpace $ LBS.head $ ln M.<> "\n" of
True -> put ctx ln
False -> adjust_le (M.<>ln) <$> close_test_exe ctx te
where
= matchSource mtch
ln = allMatches mtchs !! 0
mtch
test_exe_gen :: Bool
-> Bool
-> Ctx
-> LineNo
-> Matches LBS.ByteString
-> IO (LineEdit LBS.ByteString)
= do
test_exe_gen is_t is_e ctx _ mtchs <- readIORef (_ctx_test_exe ctx)
mb <- maybe (return Delete) (close_test_exe ctx) mb
le $ Just $
writeIORef (_ctx_test_exe ctx) TestExe
= is_t
{ _te_test = is_e
, _te_exe = i
, _te_name = ""
, _te_text
}return le
where
= captureText [cp|i|] mtch
i
= allMatches mtchs !! 0
mtch
close_test_exe :: Ctx -> TestExe -> IO (LineEdit LBS.ByteString)
@Ctx{..} te = do
close_test_exe ctxNothing
writeIORef _ctx_test_exe $ mconcat $ concat $
put ctx False te "Executable" | _te_exe te ]
[ [ mk_test_exe True te "Test-Suite" | _te_test te ]
, [ mk_test_exe
]
put :: Ctx -> LBS.ByteString -> IO (LineEdit LBS.ByteString)
Ctx{..} lbs = do
put <- readIORef _ctx_test_exe
mb case mb of
Nothing -> return $ ReplaceWith lbs
Just te -> do
$ Just te { _te_text = _te_text te M.<> lbs M.<> "\n" }
writeIORef _ctx_test_exe return Delete
mk_test_exe :: Bool -> TestExe -> LBS.ByteString -> LBS.ByteString
= (M.<> _te_text te) $ LBS.unlines $ concat
mk_test_exe is_t te te_lbs_kw $ printf "%s %s" (LBS.unpack te_lbs_kw) nm ]
[ [ LBS.pack " type: exitcode-stdio-1.0" | is_t ]
, [
]where
= case is_t of
nm True -> LBS.unpack $ _te_name te M.<> "-test"
False -> LBS.unpack $ _te_name te
mk_build_depends :: Bool
-> Bool
-> Bool
-> Map.Map LBS.ByteString LBS.ByteString
-> [LBS.ByteString]
-> LBS.ByteString
= LBS.unlines $
mk_build_depends lb we fp mp pks0 " Default-Language: Haskell2010"
[ ""
, ++ filter (if lb then const True else const False)
] " Other-Extensions:"
[ " AllowAmbiguousTypes"
, " CPP"
, " DeriveDataTypeable"
, " DeriveGeneric"
, " ExistentialQuantification"
, " FlexibleContexts"
, " FlexibleInstances"
, " FunctionalDependencies"
, " GeneralizedNewtypeDeriving"
, " MultiParamTypeClasses"
, " NoImplicitPrelude"
, " OverloadedStrings"
, " QuasiQuotes"
, " RecordWildCards"
, " ScopedTypeVariables"
, " TemplateHaskell"
, " TypeSynonymInstances"
, " UndecidableInstances"
, ""
, " if !impl(ghc >= 8.0)"
, " Other-Extensions: TemplateHaskell"
, " else"
, " Other-Extensions: TemplateHaskellQuotes"
, ""
, ++
] " GHC-Options:"
[ " -Wall"
, " -fwarn-tabs"
, " " M.<> w_error_or_warn
, ""
, " Build-depends:"
, ++ (map fmt $ zip (True : repeat False) $ L.sortBy comp pks)
] where
= case we of
w_error_or_warn True -> "-Werror"
False -> "-Wwarn"
= case fp of
pks False -> pks0
True -> filter (/= "regex-with-pcre") pks0
= LBS.pack $
fmt (isf,pk) " %c %-20s %s"
printf if isf then ' ' else ',')
(
(LBS.unpack pk)maybe "" LBS.unpack $ Map.lookup pk mp)
(
= case (x=="regex",y=="regex") of
comp x y True ,True ) -> EQ
(True ,False) -> LT
(False,True ) -> GT
(False,False) -> case (x=="regex-with-pcre",y=="regex-with-pcre") of
(True ,True ) -> EQ
(True ,False) -> LT
(False,True ) -> GT
(False,False) -> compare x y
(
adjust_le :: (LBS.ByteString->LBS.ByteString)
-> LineEdit LBS.ByteString
-> LineEdit LBS.ByteString
= case le of
adjust_le f le NoEdit -> error "adjust_le: not enough context"
ReplaceWith lbs -> ReplaceWith $ f lbs
Delete -> ReplaceWith $ f ""
sdist :: IO ()
= do
sdist False "tmp"
createDirectoryIfMissing "regex" "lib/README-regex.md"
sdist' "regex-with-pcre" "lib/README-regex.md"
sdist' "regex-examples" "lib/README-regex-examples.md"
sdist' "mega-regex" "regex"
establish <- readCurrentVersion
vrn let vrn_t = T.pack $ presentVrn vrn
test_release vrn_t<- summary vrn
smy_t "tmp/commit.txt" vrn smy_t
commit_message_ $ SH.verbosely $ do
SH.shelly "git" ["add","--all"]
SH.run_ "git" ["commit","-F","tmp/commit.txt"]
SH.run_ "git" ["tag",vrn_t,"-m",smy_t]
SH.run_
sdist' :: T.Text -> SH.FilePath -> IO ()
= do
sdist' nm readme
establish nm nm$ SH.verbosely $ do
SH.shelly "README.markdown"
SH.cp readme "stack" ["sdist","--stack-yaml","stack-8.8.yaml"]
SH.run_ <- analyse_so <$> SH.lastStderr
(pth,tb) $ pth) $ SH.fromText $ "releases/" M.<> tb
SH.cp (SH.fromText where
= (mtch!$$[cp|pth|],mtch!$$[cp|tb|])
analyse_so so where
= so T.?=~
mtch
[re|^.*Wrote sdist tarball to ${pth}(.*${tb}(regex-.*\.tar\.gz))$|]
establish :: T.Text -> T.Text -> IO ()
= SH.shelly $ SH.verbosely $ do
establish nm nm' "mega-regex.cabal"
SH.rm_f "regex-with-pcre.cabal"
SH.rm_f "regex.cabal"
SH.rm_f "regex-examples.cabal"
SH.rm_f
SH.cp (SH.fromText sf) (SH.fromText df)where
= "lib/" M.<> nm M.<> ".cabal"
sf = nm' M.<> ".cabal"
df
test_release :: T.Text -> IO ()
= do
test_release vrn_t "releases"
setCurrentDirectory $ SH.verbosely $ do
SH.shelly "test-regex-examples"
SH.rm_rf "." "regex-examples"
unpack "test-regex-examples"
setCurrentDirectory $ SH.verbosely $ do
SH.shelly ".." "regex"
unpack ".." "regex-with-pcre"
unpack "../../lib/release-testing/stack.yaml" "."
SH.cp "stack" ["--no-terminal","test", "--haddock", "--no-haddock-deps"]
SH.run_ "../.."
setCurrentDirectory where
= do
unpack rp pn "tar" ["xzf",rp M.<> "/" M.<> pn_vrn M.<> ".tar.gz"]
SH.run_ $ "test-" M.<> pn)
SH.mv (SH.fromText pn_vrn) (SH.fromText where
= pn M.<> "-" M.<> vrn_t pn_vrn
commit_message :: IO ()
= do
commit_message False "tmp"
createDirectoryIfMissing <- readCurrentVersion
vrn <- summary vrn
smy_t "tmp/commit.txt" vrn smy_t
commit_message_ "tmp/commit.txt" >>= LBS.putStrLn
LBS.readFile
commit_message_ :: FilePath -> Vrn -> T.Text -> IO ()
@Vrn{..} smy_t = do
commit_message_ fp vrn<- escape ("^"++) vrn_s
rex <$> grepLines rex "changelog" >>= LBS.writeFile fp
parse_commit smy_ln where
= vrn_s ++ ": " ++ T.unpack smy_t
smy_ln = presentVrn vrn
vrn_s
parse_commit :: String -> [Line LBS.ByteString] -> LBS.ByteString
= case lns0 of
parse_commit hdr lns0 :_:ln:lns | anyMatches $ getLineMatches ln
_-> LBS.unlines $ LBS.pack hdr : map fixes (takeWhile is_bullet lns)
-> error oops
_ where
Line{..} =
is_bullet 4 (matchesSource getLineMatches) == " * "
LBS.take
Line{..} =
fixes *=~/ [ed|#${n}([0-9]+)///fixes #${n}|]
matchesSource getLineMatches
= unlines
oops "failed to parse changelog"
[ "(expected line 3 to start with the current version)"
, ]
summary :: Vrn -> IO T.Text
= do
summary vrn let vrn_res = concat
show $ _vrn_a vrn
[ "\\."
, show $ _vrn_b vrn
, "\\."
, show $ _vrn_c vrn
, "\\."
, show $ _vrn_d vrn
,
]<- compileRegex $ "- \\[[xX]\\] +@{%date} +v"++vrn_res++" +\\[?${smy}([^]]+)"
rex <- linesMatched LinesMatched <$> grepLines rex "lib/md/roadmap-incl.md"
lns case lns of
Line _ (Matches _ [mtch])] -> return $ TE.decodeUtf8 $ LBS.toStrict $ mtch !$$ [cp|smy|]
[-> error "failed to locate the summary text in the roadmap" _