Create reference files from unpacked archives with helper program

This commit is contained in:
Nikolay Yakimov 2015-03-18 22:33:16 +03:00 committed by John MacFarlane
parent 1710c4bd8b
commit d744b83b61
3 changed files with 56 additions and 5 deletions

View file

@ -22,7 +22,10 @@ import Distribution.PackageDescription (PackageDescription(..), Executable(..))
import System.Process ( rawSystem )
import System.FilePath ( (</>) )
import System.Directory ( findExecutable )
import Distribution.Simple.Utils (info)
import Distribution.Simple.Utils (info, rawSystemExit)
import Distribution.Simple.Setup
import Distribution.Simple.LocalBuildInfo
import Distribution.Verbosity
main :: IO ()
main = defaultMainWithHooks $ simpleUserHooks {
@ -30,12 +33,15 @@ main = defaultMainWithHooks $ simpleUserHooks {
hookedPreProcessors = [ppBlobSuffixHandler]
-- ensure that make-pandoc-man-pages doesn't get installed to bindir
, copyHook = \pkgdescr ->
(copyHook simpleUserHooks) pkgdescr{ executables =
[x | x <- executables pkgdescr, exeName x /= "make-pandoc-man-pages"] }
copyHook simpleUserHooks pkgdescr{ executables =
[x | x <- executables pkgdescr, exeName x `notElem` noInstall] }
, instHook = \pkgdescr ->
(instHook simpleUserHooks) pkgdescr{ executables =
[x | x <- executables pkgdescr, exeName x /= "make-pandoc-man-pages"] }
instHook simpleUserHooks pkgdescr{ executables =
[x | x <- executables pkgdescr, exeName x `notElem` noInstall] }
, postBuild = makeReferenceFiles
}
where
noInstall = ["make-pandoc-man-pages","make-reference-files"]
ppBlobSuffixHandler :: PPSuffixHandler
ppBlobSuffixHandler = ("hsb", \_ _ ->
@ -49,3 +55,13 @@ ppBlobSuffixHandler = ("hsb", \_ _ ->
Nothing -> error "hsb2hs is needed to build this program: cabal install hsb2hs"
return ()
})
makeReferenceFiles :: Args -> BuildFlags -> PackageDescription -> LocalBuildInfo -> IO ()
makeReferenceFiles _ bf _ LocalBuildInfo{buildDir=buildDir}
= mapM_
(rawSystemExit verbosity progPath . return)
referenceFormats
where
verbosity = fromFlagOrDefault normal $ buildVerbosity bf
progPath = buildDir </> "make-reference-files" </> "make-reference-files"
referenceFormats = ["docx", "odt"]

View file

@ -0,0 +1,26 @@
import System.Environment
import System.Directory
import Codec.Archive.Zip
import qualified Data.ByteString.Lazy as BS
import qualified Control.Exception as E
import System.IO.Error (isDoesNotExistError)
mkzip :: String -> IO ()
mkzip fmt = do
let dir = "data/"++fmt
output = "data/reference."++fmt
cd <- getCurrentDirectory
setCurrentDirectory dir
archive <- addFilesToArchive [OptRecursive] emptyArchive ["."]
setCurrentDirectory cd
removeIfExists output
BS.writeFile output $ fromArchive archive
removeIfExists :: FilePath -> IO ()
removeIfExists fileName = removeFile fileName `E.catch` handleExists
where handleExists e
| isDoesNotExistError e = return ()
| otherwise = E.throwIO e
main :: IO ()
main = getArgs >>= mkzip . (!!0)

View file

@ -418,6 +418,15 @@ Executable make-pandoc-man-pages
else
Buildable: False
Executable make-reference-files
Main-Is: make-reference-files.hs
Hs-Source-Dirs: data
Build-Depends: zip-archive >= 0.2.3.4 && < 0.3,
base >= 4.2 && < 5,
directory >= 1 && < 1.3,
bytestring >= 0.9 && < 0.11
Default-Language: Haskell2010
Test-Suite test-pandoc
Type: exitcode-stdio-1.0
Main-Is: test-pandoc.hs