explict export lists

A small amount of dead code removed.

All of Utility/ done now.

This commit was sponsored by Brock Spratlen on Patreon.
This commit is contained in:
Joey Hess 2019-11-23 11:07:22 -04:00
parent 960f62a564
commit 1ff889e456
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
16 changed files with 126 additions and 25 deletions

View file

@ -7,7 +7,23 @@
{-# OPTIONS_GHC -fno-warn-tabs #-}
module Utility.SafeCommand where
module Utility.SafeCommand (
CommandParam(..),
toCommand,
boolSystem,
boolSystem',
boolSystemEnv,
safeSystem,
safeSystem',
safeSystemEnv,
shellWrap,
shellEscape,
shellUnEscape,
segmentXargsOrdered,
segmentXargsUnordered,
prop_isomorphic_shellEscape,
prop_isomorphic_shellEscape_multiword,
) where
import System.Exit
import Utility.Process

View file

@ -7,7 +7,7 @@
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Utility.Scheduled.QuickCheck where
module Utility.Scheduled.QuickCheck (prop_schedule_roundtrips) where
import Utility.Scheduled
import Utility.QuickCheck

View file

@ -7,7 +7,11 @@
{-# LANGUAGE CPP #-}
module Utility.Shell where
module Utility.Shell (
shellPath,
shebang,
findShellCommand,
) where
import Utility.SafeCommand
#ifdef mingw32_HOST_OS

View file

@ -7,7 +7,12 @@
{-# OPTIONS_GHC -fno-warn-tabs #-}
module Utility.Split where
module Utility.Split (
split,
splitc,
replace,
dropFromEnd,
) where
import Data.List (intercalate)
import Data.List.Split (splitOn)

View file

@ -5,7 +5,24 @@
- License: BSD-2-clause
-}
module Utility.SshConfig where
module Utility.SshConfig (
SshConfig(..),
Comment(..),
SshSetting(..),
Indent,
Host,
Key,
Value,
parseSshConfig,
genSshConfig,
findHostConfigKey,
addToHostConfig,
modifyUserSshConfig,
changeUserSshConfig,
writeSshConfig,
setSshConfigMode,
sshDir,
) where
import Common
import Utility.UserInfo

View file

@ -11,7 +11,17 @@
{-# LANGUAGE BangPatterns #-}
module Utility.TList where
module Utility.TList (
TList,
newTList,
getTList,
setTList,
takeTList,
readTList,
consTList,
snocTList,
appendTList,
) where
import Common

View file

@ -7,7 +7,13 @@
{-# LANGUAGE OverloadedStrings #-}
module Utility.Tense where
module Utility.Tense (
Tense(..),
TenseChunk(..),
TenseText,
renderTense,
tenseWords,
) where
import qualified Data.Text as T
import Data.Text (Text)
@ -52,6 +58,3 @@ tenseWords = TenseText . go []
go c ((Tensed w1 w2):ws) =
go (Tensed (addspace w1) (addspace w2) : c) ws
addspace w = T.append w " "
unTensed :: Text -> TenseText
unTensed t = TenseText [UnTensed t]

View file

@ -5,7 +5,11 @@
- License: BSD-2-clause
-}
module Utility.ThreadLock where
module Utility.ThreadLock (
Lock,
newLock,
withLock,
) where
import Control.Concurrent.MVar

View file

@ -8,7 +8,14 @@
{-# LANGUAGE CPP #-}
module Utility.ThreadScheduler where
module Utility.ThreadScheduler (
Seconds(..),
Microseconds,
runEvery,
threadDelaySeconds,
waitForTermination,
oneSecond,
) where
import Control.Monad
import Control.Concurrent

View file

@ -5,7 +5,11 @@
- License: BSD-2-clause
-}
module Utility.TimeStamp where
module Utility.TimeStamp (
parserPOSIXTime,
parsePOSIXTime,
formatPOSIXTime,
) where
import Utility.Data

View file

@ -8,7 +8,13 @@
{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -fno-warn-tabs #-}
module Utility.Tmp where
module Utility.Tmp (
Template,
viaTmp,
withTmpFile,
withTmpFileIn,
relatedTemplate,
) where
import System.IO
import System.FilePath

View file

@ -8,7 +8,10 @@
{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -fno-warn-tabs #-}
module Utility.Tmp.Dir where
module Utility.Tmp.Dir (
withTmpDir,
withTmpDirIn,
) where
import Control.Monad.IfElse
import System.FilePath

View file

@ -7,7 +7,17 @@
{-# LANGUAGE CPP #-}
module Utility.Tor where
module Utility.Tor (
OnionPort,
OnionAddress(..),
OnionSocket,
UniqueIdent,
AppName,
connectHiddenService,
addHiddenService,
getHiddenServiceSocketFile,
torIsInstalled,
) where
import Common
import Utility.ThreadScheduler

View file

@ -5,7 +5,11 @@
- License: BSD-2-clause
-}
module Utility.Tuple where
module Utility.Tuple (
fst3,
snd3,
thd3,
) where
fst3 :: (a,b,c) -> a
fst3 (a,_,_) = a

View file

@ -5,7 +5,14 @@
- License: BSD-2-clause
-}
module Utility.Verifiable where
module Utility.Verifiable (
Secret,
HMACDigest,
Verifiable(..),
mkVerifiable,
verify,
prop_verifiable_sane,
) where
import Data.ByteString.UTF8 (fromString)
import qualified Data.ByteString as S

View file

@ -7,7 +7,14 @@
{-# LANGUAGE OverloadedStrings, CPP, RankNTypes #-}
module Utility.WebApp where
module Utility.WebApp (
browserProc,
runWebApp,
webAppSessionBackend,
checkAuthToken,
insertAuthToken,
writeHtmlShim,
) where
import Common
import Utility.Tmp
@ -19,11 +26,9 @@ import qualified Network.Wai as Wai
import Network.Wai.Handler.Warp
import Network.Wai.Handler.WarpTLS
import Network.HTTP.Types
import qualified Data.CaseInsensitive as CI
import Network.Socket
import "crypto-api" Crypto.Random
import qualified Web.ClientSession as CS
import qualified Data.ByteString as B
import qualified Data.Text as T
import qualified Data.Text.Encoding as TE
import Blaze.ByteString.Builder.Char.Utf8 (fromText)
@ -119,9 +124,6 @@ getSocket h = do
listen sock maxListenQueue
return sock
lookupRequestField :: CI.CI B.ByteString -> Wai.Request -> B.ByteString
lookupRequestField k req = fromMaybe "" . lookup k $ Wai.requestHeaders req
{- Rather than storing a session key on disk, use a random key
- that will only be valid for this run of the webapp. -}
webAppSessionBackend :: Yesod.Yesod y => y -> IO (Maybe Yesod.SessionBackend)
@ -188,7 +190,6 @@ insertAuthToken extractAuthToken predicate webapp root pathbits params =
writeHtmlShim :: String -> String -> FilePath -> IO ()
writeHtmlShim title url file = viaTmp writeFileProtected file $ genHtmlShim title url
{- TODO: generate this static file using Yesod. -}
genHtmlShim :: String -> String -> String
genHtmlShim title url = unlines
[ "<html>"