Command line utilities for working with epub files (Haskell)

root / util / install.hs

1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
#! /usr/bin/env stack
{- stack runghc -}

{-# LANGUAGE ScopedTypeVariables #-}

import Control.Exception
import Control.Monad
import Data.List
import Data.Version
import Distribution.Package
import Distribution.PackageDescription hiding ( error, options )
import Distribution.PackageDescription.Parse
import Distribution.Verbosity
import Distribution.Version
import System.Console.GetOpt
import System.Directory
import System.Environment
import System.Exit
import System.FilePath
import System.Process
import Text.Printf
import Text.Read


defaultOptions :: Options
defaultOptions = Options
   { optClean = False
   , optDelete = False
   , optHelp = False
   , optLink = False
   , optPrefix = "/opt"
   , optRsrcCpVerbose = True
   , optInstType = FHS
   , optVersion = True
   }

data InstallType = Bundle | FHS deriving Eq


main :: IO ()
main = do
   -- Parse args
   (opts, _) <- parseOpts =<< getArgs

   -- User asked for help
   when (optHelp opts) $ putStrLn usageText >> exitSuccess

   -- Locate cabal file
   cabalFiles <- (filter $ isSuffixOf ".cabal") <$> getDirectoryContents "."

   when (null cabalFiles) $ do
      die "Can't continue because no cabal files were found in ."

   -- Parse the cabal file and extract things we need from it
   -- then pass a pile of what we know to a function to create the
   -- installation dirs
   dirs <- constructDirs opts . package . packageDescription
      <$> readPackageDescription normal (head cabalFiles)


   -- Perform the installation

   -- Remove existing install directory
   appDirExists <- doesDirectoryExist $ appDir dirs
   when (optDelete opts && appDirExists) $ do
      putStrLn $ "Removing existing directory " ++ (appDir dirs)
      removeDirectoryRecursive $ appDir dirs

   -- Clean before building
   when (optClean opts) $ system "stack clean" >> return ()

   -- Copy the binaries
   createDirectoryIfMissing True $ binDir dirs
   installExitCode <- system $ "stack install --local-bin-path=" ++ (binDir dirs)
   unless (ok installExitCode) $ die "Can't continue because stack install failed"

   -- Copy additional scripts
   {-
   putStrLn "Copying additional scripts"
   mapM_ (\f -> copyFile ("util" </> f) (binDir dirs </> f))
      [ "script1.sh", "script2.hs" ]
   -}

   -- Copy the license
   putStrLn "\nCopying LICENSE"
   createDirectoryIfMissing True $ docDir dirs
   copyFile "LICENSE" (docDir dirs </> "LICENSE")

   -- Copy the resources
   let rsrcDirSrc = "." </> "resources"
   rsrcsExist <- doesDirectoryExist rsrcDirSrc
   when rsrcsExist $ do
      putStrLn $ "\nCopying resources"
      copyTree (optRsrcCpVerbose opts) rsrcDirSrc (rsrcDir dirs)
      return ()

   -- Make the symlink
   when (optLink opts) $ do
      if (optInstType opts == FHS) then
         putStrLn "No link will be made because installation type is fhs"
      else if (not . optVersion $ opts) then
         putStrLn "No link will be made because the app dir already has no version part"
      else do
         printf "Making symbolic link now %s -> %s\n" (linkPath dirs) (appDir dirs)
         system $ printf "rm %s" (linkPath dirs)
         system $ printf "ln -s %s %s" (appDir dirs) (linkPath dirs)
         return ()

   exitSuccess


data Dirs = Dirs
   { appDir :: FilePath
   , linkPath :: FilePath
   , binDir :: FilePath
   , docDir :: FilePath
   , rsrcDir :: FilePath
   }


constructDirs :: Options -> PackageId -> Dirs
constructDirs opts pkgId =
   Dirs appDir' linkPath' binDir' (appDir' </> "doc") (appDir' </> "resources")

   where
      project = unPackageName . pkgName $ pkgId
      version = showVersion . pkgVersion $ pkgId
      versionPart = if optVersion opts then "-" ++ version else ""
      appDir' = case (optInstType opts) of
         Bundle -> optPrefix opts </> (project ++ versionPart)
         FHS    -> optPrefix opts </> "share" </> (project ++ versionPart)
      linkPath' = optPrefix opts </> project
      binDir' = case (optInstType opts) of
         Bundle -> appDir' </> "bin"
         FHS    -> optPrefix opts </> "bin"


{- Turn an exit code (say, from system) into a Bool
-}
ok :: ExitCode -> Bool
ok ExitSuccess = True
ok _           = False


{-
   Argument parsing code
-}

data Options = Options
   { optClean :: Bool
   , optDelete :: Bool
   , optHelp :: Bool
   , optLink :: Bool
   , optPrefix :: FilePath
   , optRsrcCpVerbose :: Bool
   , optInstType :: InstallType
   , optVersion :: Bool
   }


instance Read InstallType where
   readsPrec _ "bundle" = [(Bundle, "")]
   readsPrec _ "fhs"    = [(FHS, "")]
   readsPrec _ _        = []

instance Show InstallType where
   show Bundle = "bundle"
   show FHS = "fhs"


readInstallType :: String -> InstallType
readInstallType s =
   case (readEither s) of
      Left _ -> error $ printf "Can't continue because %s is not a valid install type\n\n%s" s usageText
      Right t -> t


options :: [OptDescr (Options -> Options)]
options =
   [ Option ['c'] ["clean"]
      (NoArg (\opts -> opts { optClean = True } ))
      ("Do 'stack clean' first." ++ (defaultText . optClean $ defaultOptions))
   , Option ['C'] ["no-clean"]
      (NoArg (\opts -> opts { optClean = False } ))
      ("Do not 'stack clean' first."
         ++ (defaultText . not . optClean $ defaultOptions))
   , Option ['d'] ["delete"]
      (NoArg (\opts -> opts { optDelete = True } ))
      ("Delete the app directory before copying files."
         ++ (defaultText . optDelete $ defaultOptions))
   , Option ['D'] ["no-delete"]
      (NoArg (\opts -> opts { optDelete = False } ))
      ("Do not delete the app directory before copying files."
         ++ (defaultText . not . optDelete $ defaultOptions))
   , Option ['h'] ["help"]
      (NoArg (\opts -> opts { optHelp = True } ))
      "This help information."
   , Option ['l'] ["link"]
      (NoArg (\opts -> opts { optLink = True } ))
      ("Create symlink PROJECT -> PROJECT-VERSION in PREFIX dir. Only useful for bundle installations. Does not work on Windows."
         ++ (defaultText . optLink $ defaultOptions))
   , Option ['L'] ["no-link"]
      (NoArg (\opts -> opts { optLink = True } ))
      ("Do not create symlink PROJECT -> PROJECT-VERSION in PREFIX dir."
         ++ (defaultText . not . optLink $ defaultOptions))
   , Option ['p'] ["prefix"]
      (ReqArg (\s opts -> opts { optPrefix = s } ) "PREFIX" )
      (printf "Install prefix directory. Defaults to %s so what you'll end up with is %s/PROJECT-VERSION"
         (optPrefix defaultOptions) (optPrefix defaultOptions))
   , Option ['r'] ["resource-copy-verbose"]
      (NoArg (\opts -> opts { optRsrcCpVerbose = True } ))
      ("Be chatty when copying the resources directory."
         ++ (defaultText . optRsrcCpVerbose $ defaultOptions))
   , Option ['R'] ["no-resource-copy-verbose"]
      (NoArg (\opts -> opts { optRsrcCpVerbose = False } ))
      ("Don't be chatty when copying the resources directory. Useful when there are a LOT of resources."
         ++ (defaultText . not . optRsrcCpVerbose $ defaultOptions))
   , Option ['t'] ["type"]
      (ReqArg (\s opts -> opts { optInstType = readInstallType s } ) "INST_TYPE" )
      (printf "Installation type, see INSTALLATION TYPE below for details. Default: %s"
         (show . optInstType $ defaultOptions))
   , Option ['v'] ["version"]
      (NoArg (\opts -> opts { optVersion = True } ))
      (printf "Include version in installation path, meaning: %s/PROJECT-VERSION %s"
         (optPrefix defaultOptions) (defaultText . optVersion $ defaultOptions))
   , Option ['V'] ["no-version"]
      (NoArg (\opts -> opts { optVersion = False } ))
      (printf "Do not include version in installation path, meaning: %s/PROJECT %s"
         (optPrefix defaultOptions) (defaultText . not . optVersion $ defaultOptions))
   ]


defaultText :: Bool -> String
defaultText True  = " Default"
defaultText False = ""


parseOpts :: [String] -> IO (Options, [String])
parseOpts args =
   case getOpt Permute options args of
      (o,n,[]  ) -> return (foldl (flip id) defaultOptions o, n)
      (_,_,errs) -> ioError $ userError (concat errs ++ usageText)


usageText :: String
usageText = (usageInfo header options) ++ "\n" ++ footer
   where
      header = init $ unlines
         [ "Usage: install.hs [OPTIONS]"
         , ""
         , "options:"
         ]
      footer = init $ unlines
         [ "INSTALLATION TYPE"
         , ""
         , "This is the topology used when copying files, one of: bundle, fhs"
         , ""
         , "bundle is sort-of a self-contained structure like this:"
         , ""
         , "  $PREFIX/"
         , "    $PROJECT -> $PROJECT-$VERSION    <-- if --link was specified"
         , "    $PROJECT-$VERSION/    <-- this is the \"app directory\""
         , "      bin/..."
         , "      doc/LICENSE"
         , "      resources/..."
         , ""
         , "fhs is the more traditional UNIX structure like this:"
         , ""
         , "  $PREFIX/"
         , "    bin/..."
         , "    share/"
         , "      $PROJECT-$VERSION/  <-- this is the \"app directory\""
         , "        doc/LICENSE"
         , "        resources/..."
         , ""
         , "Be aware that when the --delete switch is used along with fhs type, the binaries WILL NOT be deleted, only the \"app directory\"."
         , ""
         , "COMPILING"
         , ""
         , "install.hs was intentionally left as a script, but if you would prefer to compile it, do this:"
         , ""
         , "  $ stack ghc -- -o util/install util/install.hs"
         , ""
         , ""
         , "This script is part of the hsinstall package by Dino Morelli <dino@ui3.info>"
         ]


{-
   Recursive file copying code

   It was desireable to have a standalone recursive file copy in
   this script for maximum cross-platform compatibility and to
   avoid Haskell library dependencies.

   Many thanks to [abuzittin gillifirca](https://codereview.stackexchange.com/users/20251/abuzittin-gillifirca) for the StackOverflow post [Copying files in Haskell](https://codereview.stackexchange.com/questions/68908/copying-files-in-haskell) where the following code was lifted.
-}

copyTree :: Bool -> FilePath -> FilePath -> IO ()
copyTree chatty s t = do
    createDirectoryIfMissing True t
    subItems <- getSubitems s
    mapM_ (copyItem chatty s t) subItems


getSubitems :: FilePath -> IO [(Bool, FilePath)]
getSubitems path = getSubitems' ""
  where
    getChildren path =  (\\ [".", ".."]) <$> getDirectoryContents path

    getSubitems' relPath = do
        let absPath = path </> relPath
        isDir <- doesDirectoryExist absPath
        children <- if isDir then getChildren absPath else return []
        let relChildren = [relPath </> p | p <- children]
        ((isDir, relPath) :) . concat <$> mapM getSubitems' relChildren


copyItem :: Bool -> FilePath -> FilePath -> (Bool, FilePath) -> IO ()
copyItem chatty baseSourcePath baseTargetPath (isDir, relativePath) = do
    let sourcePath = baseSourcePath </> relativePath
    let targetPath = baseTargetPath </> relativePath

    when chatty $
       putStrLn $ "Copying " ++ sourcePath ++ " to " ++ targetPath

    if isDir
      then createDirectoryIfMissing False targetPath
      else copyFile sourcePath targetPath