explict export lists

Eliminated some dead code. In other cases, exported a currently unused
function, since it was a logical part of the API.

Of course this improves the API documentation. It may also sometimes
let ghc optimize code better, since it can know a function is internal
to a module.

364 modules still to go, according to
git grep -E 'module [A-Za-z.]+ where'
This commit is contained in:
Joey Hess 2019-11-21 15:38:06 -04:00
parent 740e0ddbfe
commit 8ea5f3ff99
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
42 changed files with 293 additions and 69 deletions

View file

@ -7,7 +7,9 @@
- License: BSD-2-clause - License: BSD-2-clause
-} -}
module Utility.Android where module Utility.Android (
osAndroid
) where
#ifdef linux_HOST_OS #ifdef linux_HOST_OS
import Common import Common

View file

@ -5,7 +5,9 @@
- License: BSD-2-clause - License: BSD-2-clause
-} -}
module Utility.Applicative where module Utility.Applicative (
(<$$>),
) where
{- Like <$> , but supports one level of currying. {- Like <$> , but supports one level of currying.
- -

View file

@ -7,7 +7,14 @@
{-# LANGUAGE CPP #-} {-# LANGUAGE CPP #-}
module Utility.Batch where module Utility.Batch (
batch,
BatchCommandMaker,
getBatchCommandMaker,
toBatchCommand,
batchCommand,
batchCommandEnv,
) where
import Common import Common

View file

@ -7,7 +7,13 @@
{-# LANGUAGE OverloadedStrings, ScopedTypeVariables #-} {-# LANGUAGE OverloadedStrings, ScopedTypeVariables #-}
module Utility.DBus where module Utility.DBus (
ServiceName,
listServiceNames,
callDBus,
runClient,
persistentClient,
) where
import Utility.PartialPrelude import Utility.PartialPrelude
import Utility.Exception import Utility.Exception

View file

@ -7,7 +7,12 @@
{-# LANGUAGE CPP #-} {-# LANGUAGE CPP #-}
module Utility.Daemon where module Utility.Daemon (
daemonize,
foreground,
checkDaemon,
stopDaemon,
) where
import Common import Common
import Utility.PID import Utility.PID

View file

@ -7,7 +7,10 @@
{-# OPTIONS_GHC -fno-warn-tabs #-} {-# OPTIONS_GHC -fno-warn-tabs #-}
module Utility.Data where module Utility.Data (
firstJust,
eitherToMaybe,
) where
{- First item in the list that is not Nothing. -} {- First item in the list that is not Nothing. -}
firstJust :: Eq a => [Maybe a] -> Maybe a firstJust :: Eq a => [Maybe a] -> Maybe a

View file

@ -8,7 +8,7 @@
{-# LANGUAGE CPP #-} {-# LANGUAGE CPP #-}
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
module Utility.DebugLocks where module Utility.DebugLocks (debugLocks) where
import Control.Monad.Catch import Control.Monad.Catch
import Control.Monad.IO.Class import Control.Monad.IO.Class

View file

@ -11,7 +11,15 @@
{-# LANGUAGE CPP #-} {-# LANGUAGE CPP #-}
module Utility.DirWatcher where module Utility.DirWatcher (
canWatch,
eventsCoalesce,
closingTracked,
modifyTracked,
DirWatcherHandle,
watchDir,
stopWatchDir,
) where
import Utility.DirWatcher.Types import Utility.DirWatcher.Types

View file

@ -5,7 +5,7 @@
- License: BSD-2-clause - License: BSD-2-clause
-} -}
module Utility.DirWatcher.FSEvents where module Utility.DirWatcher.FSEvents (watchDir) where
import Common hiding (isDirectory) import Common hiding (isDirectory)
import Utility.DirWatcher.Types import Utility.DirWatcher.Types

View file

@ -5,7 +5,7 @@
- License: BSD-2-clause - License: BSD-2-clause
-} -}
module Utility.DirWatcher.INotify where module Utility.DirWatcher.INotify (watchDir) where
import Common hiding (isDirectory) import Common hiding (isDirectory)
import Utility.ThreadLock import Utility.ThreadLock

View file

@ -5,7 +5,11 @@
- License: BSD-2-clause - License: BSD-2-clause
-} -}
module Utility.DirWatcher.Types where module Utility.DirWatcher.Types (
Hook,
WatchHooks(..),
mkWatchHooks,
) where
import Common import Common

View file

@ -5,7 +5,7 @@
- License: BSD-2-clause - License: BSD-2-clause
-} -}
module Utility.DirWatcher.Win32Notify where module Utility.DirWatcher.Win32Notify (watchDir) where
import Common hiding (isDirectory) import Common hiding (isDirectory)
import Utility.DirWatcher.Types import Utility.DirWatcher.Types

View file

@ -9,11 +9,16 @@
{-# LANGUAGE LambdaCase #-} {-# LANGUAGE LambdaCase #-}
{-# OPTIONS_GHC -fno-warn-tabs #-} {-# OPTIONS_GHC -fno-warn-tabs #-}
module Utility.Directory.Stream where module Utility.Directory.Stream (
DirectoryHandle,
openDirectory,
closeDirectory,
readDirectory,
isDirectoryEmpty,
) where
import Control.Monad import Control.Monad
import System.FilePath import System.FilePath
import System.IO.Unsafe (unsafeInterleaveIO)
import Control.Concurrent import Control.Concurrent
import Data.Maybe import Data.Maybe
import Prelude import Prelude
@ -100,22 +105,6 @@ readDirectory hdl@(DirectoryHandle _ h fdat mv) = do
return (Just filename) return (Just filename)
#endif #endif
-- | Like getDirectoryContents, but rather than buffering the whole
-- directory content in memory, lazily streams.
--
-- This is like lazy readFile in that the handle to the directory remains
-- open until the whole list is consumed, or until the list is garbage
-- collected. So use with caution particularly when traversing directory
-- trees.
streamDirectoryContents :: FilePath -> IO [FilePath]
streamDirectoryContents d = openDirectory d >>= collect
where
collect hdl = readDirectory hdl >>= \case
Nothing -> return []
Just f -> do
rest <- unsafeInterleaveIO (collect hdl)
return (f:rest)
-- | True only when directory exists and contains nothing. -- | True only when directory exists and contains nothing.
-- Throws exception if directory does not exist. -- Throws exception if directory does not exist.
isDirectoryEmpty :: FilePath -> IO Bool isDirectoryEmpty :: FilePath -> IO Bool

View file

@ -1,11 +1,23 @@
{- a simple graphviz / dot(1) digraph description generator library {- a simple graphviz / dot(1) digraph description generator library
-
- import qualified
- -
- Copyright 2010 Joey Hess <id@joeyh.name> - Copyright 2010 Joey Hess <id@joeyh.name>
- -
- License: BSD-2-clause - License: BSD-2-clause
-} -}
module Utility.Dot where -- import qualified module Utility.Dot (
graph,
graphNode,
graphEdge,
label,
attr,
fillColor,
subGraph,
indent,
quote,
) where
{- generates a graph description from a list of lines -} {- generates a graph description from a list of lines -}
graph :: [String] -> String graph :: [String] -> String

View file

@ -7,7 +7,11 @@
{-# OPTIONS_GHC -fno-warn-tabs #-} {-# OPTIONS_GHC -fno-warn-tabs #-}
module Utility.DottedVersion where module Utility.DottedVersion (
DottedVersion,
fromDottedVersion,
normalize,
) where
import Common import Common

View file

@ -8,7 +8,14 @@
{-# LANGUAGE CPP #-} {-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -fno-warn-tabs #-} {-# OPTIONS_GHC -fno-warn-tabs #-}
module Utility.Env where module Utility.Env (
getEnv,
getEnvDefault,
getEnvironment,
addEntry,
addEntries,
delEntry,
) where
#ifdef mingw32_HOST_OS #ifdef mingw32_HOST_OS
import Utility.Exception import Utility.Exception

View file

@ -7,7 +7,10 @@
{-# OPTIONS_GHC -fno-warn-tabs #-} {-# OPTIONS_GHC -fno-warn-tabs #-}
module Utility.Env.Basic where module Utility.Env.Basic (
getEnv,
getEnvDefault,
) where
import Utility.Exception import Utility.Exception
import Control.Applicative import Control.Applicative

View file

@ -7,7 +7,10 @@
{-# LANGUAGE CPP #-} {-# LANGUAGE CPP #-}
module Utility.Env.Set where module Utility.Env.Set (
setEnv,
unsetEnv,
) where
#ifdef mingw32_HOST_OS #ifdef mingw32_HOST_OS
import qualified System.SetEnv import qualified System.SetEnv

View file

@ -5,7 +5,11 @@
{-# LANGUAGE CPP #-} {-# LANGUAGE CPP #-}
module Utility.FileSize where module Utility.FileSize (
FileSize,
getFileSize,
getFileSize',
) where
import System.PosixCompat.Files import System.PosixCompat.Files
#ifdef mingw32_HOST_OS #ifdef mingw32_HOST_OS

View file

@ -7,7 +7,32 @@
{-# LANGUAGE CPP #-} {-# LANGUAGE CPP #-}
module Utility.Gpg where module Utility.Gpg (
KeyId,
KeyIds(..),
GpgCmd(..),
mkGpgCmd,
boolGpgCmd,
pkEncTo,
stdEncryptionParams,
pipeStrict,
feedRead,
pipeLazy,
findPubKeys,
UserId,
secretKeys,
KeyType(..),
maxRecommendedKeySize,
genSecretKey,
genRandom,
testKeyId,
#ifndef mingw32_HOST_OS
testHarness,
testTestHarness,
checkEncryptionFile,
checkEncryptionStream,
#endif
) where
import Common import Common
import qualified BuildInfo import qualified BuildInfo
@ -279,6 +304,7 @@ genRandom cmd highQuality size = checksize <$> readStrict cmd params
- It has an empty passphrase. -} - It has an empty passphrase. -}
testKeyId :: String testKeyId :: String
testKeyId = "129D6E0AC537B9C7" testKeyId = "129D6E0AC537B9C7"
testKey :: String testKey :: String
testKey = keyBlock True testKey = keyBlock True
[ "mI0ETvFAZgEEAKnqwWgZqznMhi1RQExem2H8t3OyKDxaNN3rBN8T6LWGGqAYV4wT" [ "mI0ETvFAZgEEAKnqwWgZqznMhi1RQExem2H8t3OyKDxaNN3rBN8T6LWGGqAYV4wT"
@ -299,6 +325,7 @@ testKey = keyBlock True
, "+gQkDF9/" , "+gQkDF9/"
, "=1k11" , "=1k11"
] ]
testSecretKey :: String testSecretKey :: String
testSecretKey = keyBlock False testSecretKey = keyBlock False
[ "lQHYBE7xQGYBBACp6sFoGas5zIYtUUBMXpth/Ldzsig8WjTd6wTfE+i1hhqgGFeM" [ "lQHYBE7xQGYBBACp6sFoGas5zIYtUUBMXpth/Ldzsig8WjTd6wTfE+i1hhqgGFeM"
@ -332,6 +359,7 @@ testSecretKey = keyBlock False
, "IJf+/dFjxEmflWpbxw/36pEd/EReLX8b8qDIYadK6BpiWN9xgEiBv/oEJAxffw==" , "IJf+/dFjxEmflWpbxw/36pEd/EReLX8b8qDIYadK6BpiWN9xgEiBv/oEJAxffw=="
, "=LDsg" , "=LDsg"
] ]
keyBlock :: Bool -> [String] -> String keyBlock :: Bool -> [String] -> String
keyBlock public ls = unlines keyBlock public ls = unlines
[ "-----BEGIN PGP "++t++" KEY BLOCK-----" [ "-----BEGIN PGP "++t++" KEY BLOCK-----"
@ -381,9 +409,7 @@ testTestHarness :: FilePath -> GpgCmd -> IO Bool
testTestHarness tmpdir cmd = do testTestHarness tmpdir cmd = do
keys <- testHarness tmpdir cmd $ findPubKeys cmd testKeyId keys <- testHarness tmpdir cmd $ findPubKeys cmd testKeyId
return $ KeyIds [testKeyId] == keys return $ KeyIds [testKeyId] == keys
#endif
#ifndef mingw32_HOST_OS
checkEncryptionFile :: GpgCmd -> FilePath -> Maybe KeyIds -> IO Bool checkEncryptionFile :: GpgCmd -> FilePath -> Maybe KeyIds -> IO Bool
checkEncryptionFile cmd filename keys = checkEncryptionFile cmd filename keys =
checkGpgPackets cmd keys =<< readStrict cmd params checkGpgPackets cmd keys =<< readStrict cmd params

View file

@ -5,7 +5,11 @@
- License: BSD-2-clause - License: BSD-2-clause
-} -}
module Utility.HtmlDetect where module Utility.HtmlDetect (
isHtml,
isHtmlBs,
htmlPrefixLength,
) where
import Text.HTML.TagSoup import Text.HTML.TagSoup
import Data.Char import Data.Char

View file

@ -5,7 +5,7 @@
- License: BSD-2-clause - License: BSD-2-clause
-} -}
module Utility.HumanNumber where module Utility.HumanNumber (showImprecise) where
{- Displays a fractional value as a string with a limited number {- Displays a fractional value as a string with a limited number
- of decimal digits. -} - of decimal digits. -}

View file

@ -5,7 +5,12 @@
- License: BSD-2-clause - License: BSD-2-clause
-} -}
module Utility.IPAddress where module Utility.IPAddress (
extractIPAddress,
isLoopbackAddress,
isPrivateAddress,
makeAddressMatcher,
) where
import Utility.Exception import Utility.Exception

View file

@ -5,7 +5,11 @@
- License: BSD-2-clause - License: BSD-2-clause
-} -}
module Utility.LinuxMkLibs where module Utility.LinuxMkLibs (
installLib,
parseLdd,
glibcLibs,
) where
import Utility.PartialPrelude import Utility.PartialPrelude
import Utility.Directory import Utility.Directory

View file

@ -5,7 +5,7 @@
- License: BSD-2-clause - License: BSD-2-clause
-} -}
module Utility.LockFile.LockStatus where module Utility.LockFile.LockStatus (LockStatus(..)) where
import System.Posix import System.Posix

View file

@ -7,7 +7,15 @@
{-# LANGUAGE CPP #-} {-# LANGUAGE CPP #-}
module Utility.LogFile where module Utility.LogFile (
openLog,
listLogs,
maxLogs,
#ifndef mingw32_HOST_OS
redirLog,
redir,
#endif
) where
import Common import Common

View file

@ -5,7 +5,12 @@
- License: BSD-2-clause - License: BSD-2-clause
-} -}
module Utility.Lsof where module Utility.Lsof (
LsofOpenMode(..),
setup,
queryDir,
query,
) where
import Common import Common
import BuildInfo import BuildInfo

View file

@ -7,7 +7,40 @@
{-# LANGUAGE TypeSynonymInstances, BangPatterns #-} {-# LANGUAGE TypeSynonymInstances, BangPatterns #-}
module Utility.Metered where module Utility.Metered (
MeterUpdate,
nullMeterUpdate,
combineMeterUpdate,
BytesProcessed(..),
toBytesProcessed,
fromBytesProcessed,
addBytesProcessed,
zeroBytesProcessed,
withMeteredFile,
meteredWrite,
meteredWrite',
meteredWriteFile,
offsetMeterUpdate,
hGetContentsMetered,
hGetMetered,
defaultChunkSize,
watchFileSize,
OutputHandler(..),
ProgressParser,
commandMeter,
commandMeter',
demeterCommand,
demeterCommandEnv,
avoidProgress,
rateLimitMeterUpdate,
Meter,
mkMeter,
setMeterTotalSize,
updateMeter,
displayMeterHandle,
clearMeterHandle,
bandwidthMeter,
) where
import Common import Common
import Utility.Percentage import Utility.Percentage
@ -80,11 +113,6 @@ withMeteredFile :: FilePath -> MeterUpdate -> (L.ByteString -> IO a) -> IO a
withMeteredFile f meterupdate a = withBinaryFile f ReadMode $ \h -> withMeteredFile f meterupdate a = withBinaryFile f ReadMode $ \h ->
hGetContentsMetered h meterupdate >>= a hGetContentsMetered h meterupdate >>= a
{- Sends the content of a file to a Handle, updating the meter as it's
- written. -}
streamMeteredFile :: FilePath -> MeterUpdate -> Handle -> IO ()
streamMeteredFile f meterupdate h = withMeteredFile f meterupdate $ L.hPut h
{- Writes a ByteString to a Handle, updating a meter as it's written. -} {- Writes a ByteString to a Handle, updating a meter as it's written. -}
meteredWrite :: MeterUpdate -> Handle -> L.ByteString -> IO () meteredWrite :: MeterUpdate -> Handle -> L.ByteString -> IO ()
meteredWrite meterupdate h = void . meteredWrite' meterupdate h meteredWrite meterupdate h = void . meteredWrite' meterupdate h

View file

@ -7,7 +7,19 @@
{-# OPTIONS_GHC -fno-warn-tabs #-} {-# OPTIONS_GHC -fno-warn-tabs #-}
module Utility.Misc where module Utility.Misc (
hGetContentsStrict,
readFileStrict,
separate,
firstLine,
segment,
segmentDelim,
massReplace,
hGetSomeString,
exitBool,
prop_segment_regressionTest,
) where
import System.IO import System.IO
import Control.Monad import Control.Monad

View file

@ -7,7 +7,19 @@
{-# OPTIONS_GHC -fno-warn-tabs #-} {-# OPTIONS_GHC -fno-warn-tabs #-}
module Utility.Monad where module Utility.Monad (
firstM,
getM,
anyM,
allM,
untilTrue,
ifM,
(<||>),
(<&&>),
observe,
after,
noop,
) where
import Data.Maybe import Data.Maybe
import Control.Monad import Control.Monad

View file

@ -7,7 +7,7 @@
{-# OPTIONS_GHC -fno-warn-tabs #-} {-# OPTIONS_GHC -fno-warn-tabs #-}
module Utility.Network where module Utility.Network (getHostname) where
import Utility.Process import Utility.Process
import Utility.Exception import Utility.Exception

View file

@ -7,7 +7,12 @@
{-# OPTIONS_GHC -fno-warn-tabs #-} {-# OPTIONS_GHC -fno-warn-tabs #-}
module Utility.OSX where module Utility.OSX (
autoStartBase,
systemAutoStart,
userAutoStart,
genOSXAutoStartFile,
) where
import Utility.UserInfo import Utility.UserInfo

View file

@ -5,7 +5,10 @@
- License: BSD-2-clause - License: BSD-2-clause
-} -}
module Utility.OptParse where module Utility.OptParse (
invertableSwitch,
invertableSwitch',
) where
import Options.Applicative import Options.Applicative
import Data.Monoid import Data.Monoid

View file

@ -7,7 +7,7 @@
{-# LANGUAGE CPP #-} {-# LANGUAGE CPP #-}
module Utility.PID where module Utility.PID (PID, getPID) where
#ifndef mingw32_HOST_OS #ifndef mingw32_HOST_OS
import System.Posix.Types (ProcessID) import System.Posix.Types (ProcessID)

View file

@ -5,7 +5,7 @@
- License: BSD-2-clause - License: BSD-2-clause
-} -}
module Utility.Parallel where module Utility.Parallel (inParallel) where
import Common import Common

View file

@ -7,7 +7,18 @@
{-# OPTIONS_GHC -fno-warn-tabs #-} {-# OPTIONS_GHC -fno-warn-tabs #-}
module Utility.PartialPrelude where module Utility.PartialPrelude (
Utility.PartialPrelude.read,
Utility.PartialPrelude.head,
Utility.PartialPrelude.tail,
Utility.PartialPrelude.init,
Utility.PartialPrelude.last,
Utility.PartialPrelude.readish,
Utility.PartialPrelude.headMaybe,
Utility.PartialPrelude.lastMaybe,
Utility.PartialPrelude.beginning,
Utility.PartialPrelude.end,
) where
import qualified Data.Maybe import qualified Data.Maybe

View file

@ -8,7 +8,29 @@
{-# LANGUAGE CPP #-} {-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -fno-warn-tabs #-} {-# OPTIONS_GHC -fno-warn-tabs #-}
module Utility.Path where module Utility.Path (
simplifyPath,
absPathFrom,
parentDir,
upFrom,
dirContains,
absPath,
relPathCwdToFile,
relPathDirToFile,
relPathDirToFileAbs,
segmentPaths,
runSegmentPaths,
relHome,
inPath,
searchPath,
dotfile,
sanitizeFilePath,
splitShortExtensions,
prop_upFrom_basics,
prop_relPathDirToFile_basics,
prop_relPathDirToFile_regressionTest,
) where
import System.FilePath import System.FilePath
import Data.List import Data.List

View file

@ -8,7 +8,7 @@
{-# LANGUAGE CPP #-} {-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -fno-warn-tabs #-} {-# OPTIONS_GHC -fno-warn-tabs #-}
module Utility.Path.Max where module Utility.Path.Max (fileNameLengthLimit) where
#ifndef mingw32_HOST_OS #ifndef mingw32_HOST_OS
import Utility.Exception import Utility.Exception

View file

@ -8,7 +8,11 @@
{-# LANGUAGE CPP #-} {-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -fno-warn-tabs #-} {-# OPTIONS_GHC -fno-warn-tabs #-}
module Utility.Process.Transcript where module Utility.Process.Transcript (
processTranscript,
processTranscript',
processTranscript'',
) where
import Utility.Process import Utility.Process
import Utility.Misc import Utility.Misc

View file

@ -7,7 +7,17 @@
{-# LANGUAGE CPP #-} {-# LANGUAGE CPP #-}
module Utility.Rsync where module Utility.Rsync (
rsyncShell,
rsyncServerSend,
rsyncServerReceive,
rsyncUseDestinationPermissions,
rsync,
rsyncUrlIsShell,
rsyncUrlIsPath,
rsyncProgress,
filterRsyncSafeOptions,
) where
import Common import Common
import Utility.Metered import Utility.Metered
@ -161,10 +171,8 @@ filterRsyncSafeOptions = fst3 . getOpt Permute
- The virtual filesystem contains: - The virtual filesystem contains:
- /c, /d, ... mount points for Windows drives - /c, /d, ... mount points for Windows drives
-} -}
#ifdef mingw32_HOST_OS
toMSYS2Path :: FilePath -> FilePath toMSYS2Path :: FilePath -> FilePath
#ifndef mingw32_HOST_OS
toMSYS2Path = id
#else
toMSYS2Path p toMSYS2Path p
| null drive = recombine parts | null drive = recombine parts
| otherwise = recombine $ "/" : driveletter drive : parts | otherwise = recombine $ "/" : driveletter drive : parts

View file

@ -7,7 +7,15 @@
{-# LANGUAGE CPP #-} {-# LANGUAGE CPP #-}
module Utility.Su where module Utility.Su (
WhosePassword(..),
PasswordPrompt(..),
describePasswordPrompt,
describePasswordPrompt',
SuCommand,
runSuCommand,
mkSuCommand,
) where
import Common import Common

View file

@ -445,7 +445,7 @@ downloadConduit meterupdate req file uo =
liftIO $ debugM "url" (show req'') liftIO $ debugM "url" (show req'')
resp <- http req'' (httpManager uo) resp <- http req'' (httpManager uo)
if responseStatus resp == partialContent206 if responseStatus resp == partialContent206
then store (BytesProcessed sz) AppendMode resp then store (toBytesProcessed sz) AppendMode resp
else if responseStatus resp == ok200 else if responseStatus resp == ok200
then store zeroBytesProcessed WriteMode resp then store zeroBytesProcessed WriteMode resp
else respfailure resp else respfailure resp