Skip to content

Commit

Permalink
library: make all exports explicit
Browse files Browse the repository at this point in the history
  • Loading branch information
andreasabel committed Feb 12, 2022
1 parent ee252ec commit 1aa173e
Show file tree
Hide file tree
Showing 35 changed files with 376 additions and 130 deletions.
2 changes: 1 addition & 1 deletion src/Control/Concurrent/Thread/Utils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,7 @@ module Control.Concurrent.Thread.Utils(-- * I\/O utilities
)
where

import Control.Concurrent
import safe Control.Concurrent ( forkIO, ThreadId )

{- | Takes a IO action and a function. The IO action will be called in a
separate thread. When it is completed, the specified function is called with
Expand Down
3 changes: 2 additions & 1 deletion src/Data/BinPacking.hs
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,8 @@ module Data.BinPacking (BinPacker,
)

where
import Data.List

import Data.List (sortOn)
import Control.Monad.Error

{- | Potential errors returned as Left values by 'BinPacker' functions.
Expand Down
5 changes: 3 additions & 2 deletions src/Data/Bits/Utils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,8 +23,9 @@ Written by John Goerzen, jgoerzen\@complete.org
module Data.Bits.Utils(getBytes, fromBytes,
c2w8, s2w8, w82c, w82s)
where
import Data.Bits
import Data.Word
import safe Data.Bits
( Bits((.|.), (.&.), shiftR, bitSizeMaybe, shiftL) )
import safe Data.Word ( Word8 )

{- | Returns a list representing the bytes that comprise a data type.
Expand Down
13 changes: 12 additions & 1 deletion src/Data/CSV.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,18 @@ Written by John Goerzen, jgoerzen\@complete.org
-}

module Data.CSV (csvFile, genCsvFile) where
import Text.ParserCombinators.Parsec
import safe Text.ParserCombinators.Parsec
( char,
noneOf,
string,
endBy,
sepBy,
(<?>),
(<|>),
many,
try,
GenParser,
CharParser )
import Data.List (intersperse)

eol :: forall st. GenParser Char st String
Expand Down
13 changes: 7 additions & 6 deletions src/Data/Compression/Inflate.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,15 +32,16 @@ module Data.Compression.Inflate (inflate_string,
inflate, Output, Bit,
bits_to_word32) where

import Control.Applicative
import Control.Monad
import Data.Array
import safe Control.Monad ( ap, unless )
import safe Data.Array ( Array, array, (!), (//) )
import qualified Data.Char
import Data.List
import Data.Maybe
( mapAccumL, genericDrop, genericReplicate, genericSplitAt, genericTake
, sort )
import safe Data.Maybe ()

import Data.Bits
import Data.Word
import safe Data.Bits ( Bits(testBit) )
import safe Data.Word ( Word8, Word32 )

inflate_string :: String -> String
inflate_string = fst . inflate_string_remainder
Expand Down
9 changes: 4 additions & 5 deletions src/Data/Hash/CRC32/GZip.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,11 +23,10 @@ RFC1952.

module Data.Hash.CRC32.GZip where

import Data.Array
import Data.Bits
import Data.Char
import Data.List
import Data.Word
import safe Data.Array ( Array, array, (!) )
import safe Data.Bits ( Bits(xor, (.&.), shiftR) )
import safe Data.Char ( ord )
import safe Data.Word ( Word32 )

update_crc :: Word32 -> Char -> Word32
update_crc crc ch =
Expand Down
6 changes: 3 additions & 3 deletions src/Data/Hash/MD5.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,9 +28,9 @@ module Data.Hash.MD5
, WordList(..)
) where

import Data.Bits
import Data.Char (chr, ord)
import Data.Word
import safe Data.Bits (Bits (complement, rotateL, shiftL, shiftR, xor, (.&.), (.|.)))
import safe Data.Char (chr, ord)
import safe Data.Word (Word32, Word64)

-- | Synonym for 'Word64' due to historic reasons
type Zord64 = Word64
Expand Down
4 changes: 2 additions & 2 deletions src/Data/Hash/MD5/Zord64_HARD.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,8 +6,8 @@
-- | Obsolete legacy module
module Data.Hash.MD5.Zord64_HARD (Zord64) where

import Data.Bits
import Data.Word
import safe Data.Bits ( Bits(complement, (.&.), (.|.), shift) )
import safe Data.Word ( Word32 )

data Zord64 = W64 {lo,hi::Word32} deriving (Eq, Ord, Bounded)

Expand Down
7 changes: 3 additions & 4 deletions src/Data/List/Utils.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# LANGUAGE Safe #-}

{- arch-tag: List utilities main file
Copyright (c) 2004-2011 John Goerzen <jgoerzen@complete.org>
Expand Down Expand Up @@ -48,13 +49,11 @@ module Data.List.Utils(-- * Merging
-- -- * Sub-List Selection
-- sub,
) where

import Control.Monad.State (State, get, put)
import Data.List (concat, elemIndex, elemIndices,
elemIndices, find, findIndex,
intercalate, intersperse,
import Data.List (elemIndices, findIndex, intercalate,
isInfixOf, isPrefixOf, isSuffixOf, nub,
tails)
import Data.Maybe (isJust)


{- | Merge two sorted lists into a single, sorted whole.
Expand Down
15 changes: 8 additions & 7 deletions src/Data/MIME/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -37,13 +37,14 @@ where

import qualified Data.Map as Map
import qualified Control.Exception (try, IOException)
import Control.Monad
import System.IO
import System.IO.Error
import System.IO.Utils
import System.Path
import Data.Map.Utils
import Data.Char
import safe Control.Monad ( foldM )
import safe System.IO
( Handle, hClose, openFile, IOMode(ReadMode) )
import safe System.IO.Error ()
import safe System.IO.Utils ( hGetLines )
import safe System.Path ( splitExt )
import safe Data.Map.Utils ( flippedLookupM )
import safe Data.Char ( toLower )

----------------------------------------------------------------------
-- Basic type declarations
Expand Down
20 changes: 17 additions & 3 deletions src/Data/Progress/Meter.hs
Original file line number Diff line number Diff line change
Expand Up @@ -40,13 +40,27 @@ module Data.Progress.Meter (-- * Types
killAutoDisplayMeter
) where

import Data.Progress.Tracker
import Control.Concurrent
import safe Data.Progress.Tracker
( ProgressStatuses(..),
Progress,
ProgressStatus(totalUnits, completedUnits, trackerName),
getSpeed,
getETR )
import safe Control.Concurrent
( modifyMVar_,
withMVar,
newMVar,
MVar,
threadDelay,
forkIO,
myThreadId,
yield,
ThreadId )
import Control.Monad (when)
import Data.String.Utils (join)
import System.Time.Utils (renderSecs)
import Data.Quantity (renderNums, binaryOpts)
import System.IO
import safe System.IO ( Handle, hFlush, hPutStr )
import Control.Monad (filterM)

{- | The main data type for the progress meter. -}
Expand Down
9 changes: 5 additions & 4 deletions src/Data/Progress/Tracker.hs
Original file line number Diff line number Diff line change
Expand Up @@ -47,10 +47,11 @@ module Data.Progress.Tracker (
)

where
import Control.Concurrent.MVar
import System.Time
import System.Time.Utils
import Data.Ratio
import safe Control.Concurrent.MVar
( modifyMVar_, withMVar, newMVar, MVar )
import safe System.Time ( getClockTime )
import safe System.Time.Utils ( clockTimeToEpoch )
import safe Data.Ratio ( (%) )

{- $introduction
Expand Down
6 changes: 3 additions & 3 deletions src/Data/Quantity.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,9 +32,9 @@ module Data.Quantity (
)

where
import Data.Char
import Data.List
import Text.Printf
import safe Data.Char ( toLower )
import safe Data.List (find)
import safe Text.Printf ( printf )

{- | The options for 'quantifyNum' and 'renderNum' -}
data SizeOpts = SizeOpts { base :: Int, -- ^ The base from which calculations are made
Expand Down
9 changes: 5 additions & 4 deletions src/Network/Email/Sendmail.hs
Original file line number Diff line number Diff line change
Expand Up @@ -31,10 +31,11 @@ where
module Network.Email.Sendmail(sendmail)
where

import System.Cmd.Utils
import System.Directory
import System.IO
import System.IO.Error
import safe System.Cmd.Utils ( PipeMode(WriteToPipe), pOpen )
import safe System.Directory
( doesFileExist, getPermissions, Permissions(executable) )
import safe System.IO ( hPutStr )
import safe System.IO.Error ()
import qualified Control.Exception(try, IOException)

sendmails :: [String]
Expand Down
29 changes: 24 additions & 5 deletions src/Network/SocketServer.hs
Original file line number Diff line number Diff line change
Expand Up @@ -45,11 +45,30 @@ module Network.SocketServer(-- * Generic Options and Types
handleHandler
)
where
import Control.Concurrent
import Network.BSD
import Network.Socket
import Network.Utils
import System.IO
import Control.Concurrent ( forkIO )
import Data.Functor (void)
import Network.BSD
( getProtocolNumber, Family(AF_INET), HostAddress, PortNumber )
import Network.Socket
( socketToHandle,
setSocketOption,
accept,
bind,
getSocketName,
listen,
socket,
close,
SocketOption(ReuseAddr),
SockAddr(SockAddrInet),
Socket,
SocketType(Stream) )
import Network.Utils ( showSockAddr )
import System.IO
( Handle,
hClose,
hSetBuffering,
BufferMode(LineBuffering),
IOMode(ReadWriteMode) )
import qualified System.Log.Logger

{- | Options for your server. -}
Expand Down
22 changes: 19 additions & 3 deletions src/Network/Utils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -26,9 +26,25 @@ module Network.Utils (niceSocketsDo, connectTCP, connectTCPAddr,
listenTCPAddr, showSockAddr)
where

import Network.BSD
import Network.Socket
import System.IO
import Network.BSD
( getHostByName,
getProtocolNumber,
hostAddress,
HostName,
Family(AF_INET),
PortNumber )
import Network.Socket
( getNameInfo,
withSocketsDo,
bind,
connect,
listen,
socket,
close,
NameInfoFlag(NI_NUMERICHOST),
SockAddr(SockAddrInet, SockAddrUnix),
Socket,
SocketType(Stream) )
#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__))
import qualified System.Posix.Signals
#endif
Expand Down
32 changes: 24 additions & 8 deletions src/System/Cmd/Utils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -95,18 +95,34 @@ where

-- FIXME - largely obsoleted by 6.4 - convert to wrappers.

import System.Exit
import System.Process (rawSystem)
import System.Log.Logger
import System.Exit ( ExitCode(ExitFailure, ExitSuccess) )
import System.Log.Logger ( debugM, warningM )
#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__))
import System.Posix.IO
( closeFd,
createPipe,
dupTo,
fdToHandle,
stdError,
stdInput,
stdOutput )
import System.Posix.Process
( executeFile, forkProcess, getProcessStatus, ProcessStatus(..) )
import System.Posix.Signals
import qualified System.Posix.Signals
#endif
import System.Posix.Types
import System.IO
import System.IO.Error
( addSignal,
blockSignals,
emptySignalSet,
getSignalMask,
installHandler,
setSignalMask,
sigCHLD,
sigINT,
sigQUIT,
Handler(Ignore),
Signal )
#endif
import System.Posix.Types ( Fd, ProcessID )
import System.IO ( Handle, hClose, hGetContents, hPutStr )
import Control.Concurrent(forkIO)
import Control.Exception(finally)
import qualified Control.Exception(try, IOException)
Expand Down
5 changes: 3 additions & 2 deletions src/System/Console/GetOpt/Utils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,8 +27,9 @@ module System.Console.GetOpt.Utils (parseCmdLine,
stdOptional
)
where
import System.Console.GetOpt
import System.Environment
import safe System.Console.GetOpt
( getOpt, usageInfo, ArgOrder, OptDescr )
import safe System.Environment ( getArgs )

{- | Simple command line parser -- a basic wrapper around the system's
default getOpt. See the System.Console.GetOpt manual for a description of the
Expand Down
19 changes: 14 additions & 5 deletions src/System/Daemon.hs
Original file line number Diff line number Diff line change
Expand Up @@ -42,11 +42,20 @@ module System.Daemon (
where
#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__))

import System.Directory
import System.Exit
import System.Log.Logger
import System.Posix.IO
import System.Posix.Process
import System.Directory ( setCurrentDirectory )
import System.Exit ( ExitCode(ExitSuccess) )
import System.Log.Logger ( traplogging, Priority(ERROR) )
import System.Posix.IO
( openFd,
closeFd,
defaultFileFlags,
dupTo,
stdError,
stdInput,
stdOutput,
OpenMode(ReadWrite) )
import System.Posix.Process
( createSession, exitImmediately, forkProcess )


trap :: IO a -> IO a
Expand Down
6 changes: 3 additions & 3 deletions src/System/Debian.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,9 +27,9 @@ module System.Debian (-- * Control or Similar File Utilities
)
where

import System.Exit
import System.IO.Unsafe (unsafePerformIO)
import System.Process
import System.Exit ( ExitCode(ExitFailure, ExitSuccess) )
import System.IO.Unsafe (unsafePerformIO)
import System.Process ( rawSystem )

{- | The type representing the contents of a Debian control file,
or any control-like file (such as the output from apt-cache show, etc.) -}
Expand Down
Loading

0 comments on commit 1aa173e

Please sign in to comment.