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:
parent
960f62a564
commit
1ff889e456
16 changed files with 126 additions and 25 deletions
|
@ -7,7 +7,23 @@
|
||||||
|
|
||||||
{-# OPTIONS_GHC -fno-warn-tabs #-}
|
{-# 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 System.Exit
|
||||||
import Utility.Process
|
import Utility.Process
|
||||||
|
|
|
@ -7,7 +7,7 @@
|
||||||
|
|
||||||
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
||||||
|
|
||||||
module Utility.Scheduled.QuickCheck where
|
module Utility.Scheduled.QuickCheck (prop_schedule_roundtrips) where
|
||||||
|
|
||||||
import Utility.Scheduled
|
import Utility.Scheduled
|
||||||
import Utility.QuickCheck
|
import Utility.QuickCheck
|
||||||
|
|
|
@ -7,7 +7,11 @@
|
||||||
|
|
||||||
{-# LANGUAGE CPP #-}
|
{-# LANGUAGE CPP #-}
|
||||||
|
|
||||||
module Utility.Shell where
|
module Utility.Shell (
|
||||||
|
shellPath,
|
||||||
|
shebang,
|
||||||
|
findShellCommand,
|
||||||
|
) where
|
||||||
|
|
||||||
import Utility.SafeCommand
|
import Utility.SafeCommand
|
||||||
#ifdef mingw32_HOST_OS
|
#ifdef mingw32_HOST_OS
|
||||||
|
|
|
@ -7,7 +7,12 @@
|
||||||
|
|
||||||
{-# OPTIONS_GHC -fno-warn-tabs #-}
|
{-# OPTIONS_GHC -fno-warn-tabs #-}
|
||||||
|
|
||||||
module Utility.Split where
|
module Utility.Split (
|
||||||
|
split,
|
||||||
|
splitc,
|
||||||
|
replace,
|
||||||
|
dropFromEnd,
|
||||||
|
) where
|
||||||
|
|
||||||
import Data.List (intercalate)
|
import Data.List (intercalate)
|
||||||
import Data.List.Split (splitOn)
|
import Data.List.Split (splitOn)
|
||||||
|
|
|
@ -5,7 +5,24 @@
|
||||||
- License: BSD-2-clause
|
- 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 Common
|
||||||
import Utility.UserInfo
|
import Utility.UserInfo
|
||||||
|
|
|
@ -11,7 +11,17 @@
|
||||||
|
|
||||||
{-# LANGUAGE BangPatterns #-}
|
{-# LANGUAGE BangPatterns #-}
|
||||||
|
|
||||||
module Utility.TList where
|
module Utility.TList (
|
||||||
|
TList,
|
||||||
|
newTList,
|
||||||
|
getTList,
|
||||||
|
setTList,
|
||||||
|
takeTList,
|
||||||
|
readTList,
|
||||||
|
consTList,
|
||||||
|
snocTList,
|
||||||
|
appendTList,
|
||||||
|
) where
|
||||||
|
|
||||||
import Common
|
import Common
|
||||||
|
|
||||||
|
|
|
@ -7,7 +7,13 @@
|
||||||
|
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
|
|
||||||
module Utility.Tense where
|
module Utility.Tense (
|
||||||
|
Tense(..),
|
||||||
|
TenseChunk(..),
|
||||||
|
TenseText,
|
||||||
|
renderTense,
|
||||||
|
tenseWords,
|
||||||
|
) where
|
||||||
|
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
|
@ -52,6 +58,3 @@ tenseWords = TenseText . go []
|
||||||
go c ((Tensed w1 w2):ws) =
|
go c ((Tensed w1 w2):ws) =
|
||||||
go (Tensed (addspace w1) (addspace w2) : c) ws
|
go (Tensed (addspace w1) (addspace w2) : c) ws
|
||||||
addspace w = T.append w " "
|
addspace w = T.append w " "
|
||||||
|
|
||||||
unTensed :: Text -> TenseText
|
|
||||||
unTensed t = TenseText [UnTensed t]
|
|
||||||
|
|
|
@ -5,7 +5,11 @@
|
||||||
- License: BSD-2-clause
|
- License: BSD-2-clause
|
||||||
-}
|
-}
|
||||||
|
|
||||||
module Utility.ThreadLock where
|
module Utility.ThreadLock (
|
||||||
|
Lock,
|
||||||
|
newLock,
|
||||||
|
withLock,
|
||||||
|
) where
|
||||||
|
|
||||||
import Control.Concurrent.MVar
|
import Control.Concurrent.MVar
|
||||||
|
|
||||||
|
|
|
@ -8,7 +8,14 @@
|
||||||
|
|
||||||
{-# LANGUAGE CPP #-}
|
{-# LANGUAGE CPP #-}
|
||||||
|
|
||||||
module Utility.ThreadScheduler where
|
module Utility.ThreadScheduler (
|
||||||
|
Seconds(..),
|
||||||
|
Microseconds,
|
||||||
|
runEvery,
|
||||||
|
threadDelaySeconds,
|
||||||
|
waitForTermination,
|
||||||
|
oneSecond,
|
||||||
|
) where
|
||||||
|
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
import Control.Concurrent
|
import Control.Concurrent
|
||||||
|
|
|
@ -5,7 +5,11 @@
|
||||||
- License: BSD-2-clause
|
- License: BSD-2-clause
|
||||||
-}
|
-}
|
||||||
|
|
||||||
module Utility.TimeStamp where
|
module Utility.TimeStamp (
|
||||||
|
parserPOSIXTime,
|
||||||
|
parsePOSIXTime,
|
||||||
|
formatPOSIXTime,
|
||||||
|
) where
|
||||||
|
|
||||||
import Utility.Data
|
import Utility.Data
|
||||||
|
|
||||||
|
|
|
@ -8,7 +8,13 @@
|
||||||
{-# LANGUAGE CPP #-}
|
{-# LANGUAGE CPP #-}
|
||||||
{-# OPTIONS_GHC -fno-warn-tabs #-}
|
{-# OPTIONS_GHC -fno-warn-tabs #-}
|
||||||
|
|
||||||
module Utility.Tmp where
|
module Utility.Tmp (
|
||||||
|
Template,
|
||||||
|
viaTmp,
|
||||||
|
withTmpFile,
|
||||||
|
withTmpFileIn,
|
||||||
|
relatedTemplate,
|
||||||
|
) where
|
||||||
|
|
||||||
import System.IO
|
import System.IO
|
||||||
import System.FilePath
|
import System.FilePath
|
||||||
|
|
|
@ -8,7 +8,10 @@
|
||||||
{-# LANGUAGE CPP #-}
|
{-# LANGUAGE CPP #-}
|
||||||
{-# OPTIONS_GHC -fno-warn-tabs #-}
|
{-# OPTIONS_GHC -fno-warn-tabs #-}
|
||||||
|
|
||||||
module Utility.Tmp.Dir where
|
module Utility.Tmp.Dir (
|
||||||
|
withTmpDir,
|
||||||
|
withTmpDirIn,
|
||||||
|
) where
|
||||||
|
|
||||||
import Control.Monad.IfElse
|
import Control.Monad.IfElse
|
||||||
import System.FilePath
|
import System.FilePath
|
||||||
|
|
|
@ -7,7 +7,17 @@
|
||||||
|
|
||||||
{-# LANGUAGE CPP #-}
|
{-# LANGUAGE CPP #-}
|
||||||
|
|
||||||
module Utility.Tor where
|
module Utility.Tor (
|
||||||
|
OnionPort,
|
||||||
|
OnionAddress(..),
|
||||||
|
OnionSocket,
|
||||||
|
UniqueIdent,
|
||||||
|
AppName,
|
||||||
|
connectHiddenService,
|
||||||
|
addHiddenService,
|
||||||
|
getHiddenServiceSocketFile,
|
||||||
|
torIsInstalled,
|
||||||
|
) where
|
||||||
|
|
||||||
import Common
|
import Common
|
||||||
import Utility.ThreadScheduler
|
import Utility.ThreadScheduler
|
||||||
|
|
|
@ -5,7 +5,11 @@
|
||||||
- License: BSD-2-clause
|
- License: BSD-2-clause
|
||||||
-}
|
-}
|
||||||
|
|
||||||
module Utility.Tuple where
|
module Utility.Tuple (
|
||||||
|
fst3,
|
||||||
|
snd3,
|
||||||
|
thd3,
|
||||||
|
) where
|
||||||
|
|
||||||
fst3 :: (a,b,c) -> a
|
fst3 :: (a,b,c) -> a
|
||||||
fst3 (a,_,_) = a
|
fst3 (a,_,_) = a
|
||||||
|
|
|
@ -5,7 +5,14 @@
|
||||||
- License: BSD-2-clause
|
- 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 Data.ByteString.UTF8 (fromString)
|
||||||
import qualified Data.ByteString as S
|
import qualified Data.ByteString as S
|
||||||
|
|
|
@ -7,7 +7,14 @@
|
||||||
|
|
||||||
{-# LANGUAGE OverloadedStrings, CPP, RankNTypes #-}
|
{-# LANGUAGE OverloadedStrings, CPP, RankNTypes #-}
|
||||||
|
|
||||||
module Utility.WebApp where
|
module Utility.WebApp (
|
||||||
|
browserProc,
|
||||||
|
runWebApp,
|
||||||
|
webAppSessionBackend,
|
||||||
|
checkAuthToken,
|
||||||
|
insertAuthToken,
|
||||||
|
writeHtmlShim,
|
||||||
|
) where
|
||||||
|
|
||||||
import Common
|
import Common
|
||||||
import Utility.Tmp
|
import Utility.Tmp
|
||||||
|
@ -19,11 +26,9 @@ import qualified Network.Wai as Wai
|
||||||
import Network.Wai.Handler.Warp
|
import Network.Wai.Handler.Warp
|
||||||
import Network.Wai.Handler.WarpTLS
|
import Network.Wai.Handler.WarpTLS
|
||||||
import Network.HTTP.Types
|
import Network.HTTP.Types
|
||||||
import qualified Data.CaseInsensitive as CI
|
|
||||||
import Network.Socket
|
import Network.Socket
|
||||||
import "crypto-api" Crypto.Random
|
import "crypto-api" Crypto.Random
|
||||||
import qualified Web.ClientSession as CS
|
import qualified Web.ClientSession as CS
|
||||||
import qualified Data.ByteString as B
|
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
||||||
import qualified Data.Text.Encoding as TE
|
import qualified Data.Text.Encoding as TE
|
||||||
import Blaze.ByteString.Builder.Char.Utf8 (fromText)
|
import Blaze.ByteString.Builder.Char.Utf8 (fromText)
|
||||||
|
@ -119,9 +124,6 @@ getSocket h = do
|
||||||
listen sock maxListenQueue
|
listen sock maxListenQueue
|
||||||
return sock
|
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
|
{- Rather than storing a session key on disk, use a random key
|
||||||
- that will only be valid for this run of the webapp. -}
|
- that will only be valid for this run of the webapp. -}
|
||||||
webAppSessionBackend :: Yesod.Yesod y => y -> IO (Maybe Yesod.SessionBackend)
|
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 :: String -> String -> FilePath -> IO ()
|
||||||
writeHtmlShim title url file = viaTmp writeFileProtected file $ genHtmlShim title url
|
writeHtmlShim title url file = viaTmp writeFileProtected file $ genHtmlShim title url
|
||||||
|
|
||||||
{- TODO: generate this static file using Yesod. -}
|
|
||||||
genHtmlShim :: String -> String -> String
|
genHtmlShim :: String -> String -> String
|
||||||
genHtmlShim title url = unlines
|
genHtmlShim title url = unlines
|
||||||
[ "<html>"
|
[ "<html>"
|
||||||
|
|
Loading…
Reference in a new issue