aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorGravatar Joey Hess <joey@kitenet.net>2014-10-09 15:09:26 -0400
committerGravatar Joey Hess <joey@kitenet.net>2014-10-09 15:09:26 -0400
commitadb4603fbf69d8638d925627e0c85b473a3fef05 (patch)
tree789d7d7a1075d6d947143f391eca86a58f1f46ea
parenta26b7127d4cc8b2a5e15ef662ab2793dbf9e7919 (diff)
indent with tabs not spaces
Found these with: git grep "^ " $(find -type f -name \*.hs) |grep -v ': where' Unfortunately there is some inline hamlet that cannot use tabs for indentation. Also, Assistant/WebApp/Bootstrap3.hs is a copy of a module and so I'm leaving it as-is.
-rw-r--r--Annex/TaggedPush.hs10
-rw-r--r--Assistant/Threads/Watcher.hs2
-rw-r--r--Build/Standalone.hs2
-rw-r--r--Command/Fsck.hs2
-rw-r--r--Command/List.hs16
-rw-r--r--Git/DiffTree.hs2
-rw-r--r--Logs.hs6
-rw-r--r--Logs/MapLog.hs2
-rw-r--r--Logs/SingleValue.hs4
-rw-r--r--Remote/Helper/Encryptable.hs10
-rw-r--r--Remote/Helper/Special.hs2
-rw-r--r--RemoteDaemon/Types.hs2
-rw-r--r--Test.hs12
-rw-r--r--Types/Crypto.hs8
-rw-r--r--Types/ScheduledActivity.hs2
-rw-r--r--Utility/HumanTime.hs2
-rw-r--r--Utility/Scheduled.hs8
17 files changed, 46 insertions, 46 deletions
diff --git a/Annex/TaggedPush.hs b/Annex/TaggedPush.hs
index 35fdf333c..a31758022 100644
--- a/Annex/TaggedPush.hs
+++ b/Annex/TaggedPush.hs
@@ -49,13 +49,13 @@ fromTaggedBranch b = case split "/" $ Git.fromRef b of
taggedPush :: UUID -> Maybe String -> Git.Ref -> Remote -> Git.Repo -> IO Bool
taggedPush u info branch remote = Git.Command.runBool
- [ Param "push"
- , Param $ Remote.name remote
+ [ Param "push"
+ , Param $ Remote.name remote
{- Using forcePush here is safe because we "own" the tagged branch
- we're pushing; it has no other writers. Ensures it is pushed
- even if it has been rewritten by a transition. -}
- , Param $ Git.Branch.forcePush $ refspec Annex.Branch.name
- , Param $ refspec branch
- ]
+ , Param $ Git.Branch.forcePush $ refspec Annex.Branch.name
+ , Param $ refspec branch
+ ]
where
refspec b = Git.fromRef b ++ ":" ++ Git.fromRef (toTaggedBranch u info b)
diff --git a/Assistant/Threads/Watcher.hs b/Assistant/Threads/Watcher.hs
index 8482de895..2e69e1640 100644
--- a/Assistant/Threads/Watcher.hs
+++ b/Assistant/Threads/Watcher.hs
@@ -72,7 +72,7 @@ needLsof = error $ unlines
{- A special exception that can be thrown to pause or resume the watcher. -}
data WatcherControl = PauseWatcher | ResumeWatcher
- deriving (Show, Eq, Typeable)
+ deriving (Show, Eq, Typeable)
instance E.Exception WatcherControl
diff --git a/Build/Standalone.hs b/Build/Standalone.hs
index 110163acf..da030933d 100644
--- a/Build/Standalone.hs
+++ b/Build/Standalone.hs
@@ -40,7 +40,7 @@ main :: IO ()
main = getArgs >>= go
where
go [] = error "specify topdir"
- go (topdir:_) = do
+ go (topdir:_) = do
let dir = progDir topdir
createDirectoryIfMissing True dir
installed <- forM bundledPrograms $ installProg dir
diff --git a/Command/Fsck.hs b/Command/Fsck.hs
index f27f18e57..1a10a15b4 100644
--- a/Command/Fsck.hs
+++ b/Command/Fsck.hs
@@ -282,7 +282,7 @@ verifyDirectMode key file = do
- the key's metadata, if available.
-
- Not checked in direct mode, because files can be changed directly.
- -}
+ -}
checkKeySize :: Key -> Annex Bool
checkKeySize key = ifM isDirect
( return True
diff --git a/Command/List.hs b/Command/List.hs
index d038d6deb..e4d911d97 100644
--- a/Command/List.hs
+++ b/Command/List.hs
@@ -71,15 +71,15 @@ type Present = Bool
header :: [(RemoteName, TrustLevel)] -> String
header remotes = unlines (zipWith formatheader [0..] remotes) ++ pipes (length remotes)
where
- formatheader n (remotename, trustlevel) = pipes n ++ remotename ++ trust trustlevel
- pipes = flip replicate '|'
- trust UnTrusted = " (untrusted)"
- trust _ = ""
+ formatheader n (remotename, trustlevel) = pipes n ++ remotename ++ trust trustlevel
+ pipes = flip replicate '|'
+ trust UnTrusted = " (untrusted)"
+ trust _ = ""
format :: [(TrustLevel, Present)] -> FilePath -> String
format remotes file = thereMap ++ " " ++ file
where
- thereMap = concatMap there remotes
- there (UnTrusted, True) = "x"
- there (_, True) = "X"
- there (_, False) = "_"
+ thereMap = concatMap there remotes
+ there (UnTrusted, True) = "x"
+ there (_, True) = "X"
+ there (_, False) = "_"
diff --git a/Git/DiffTree.hs b/Git/DiffTree.hs
index 59de60871..489afa86c 100644
--- a/Git/DiffTree.hs
+++ b/Git/DiffTree.hs
@@ -53,7 +53,7 @@ diffIndex ref = diffIndex' ref [Param "--cached"]
diffWorkTree :: Ref -> Repo -> IO ([DiffTreeItem], IO Bool)
diffWorkTree ref repo =
ifM (Git.Ref.headExists repo)
- ( diffIndex' ref [] repo
+ ( diffIndex' ref [] repo
, return ([], return True)
)
diff --git a/Logs.hs b/Logs.hs
index 1b7a61efe..a4522bd92 100644
--- a/Logs.hs
+++ b/Logs.hs
@@ -90,11 +90,11 @@ locationLogFile key = hashDirLower key ++ keyFile key ++ ".log"
locationLogFileKey :: FilePath -> Maybe Key
locationLogFileKey path
| ["remote", "web"] `isPrefixOf` splitDirectories dir = Nothing
- | ext == ".log" = fileKey base
- | otherwise = Nothing
+ | ext == ".log" = fileKey base
+ | otherwise = Nothing
where
(dir, file) = splitFileName path
- (base, ext) = splitAt (length file - 4) file
+ (base, ext) = splitAt (length file - 4) file
{- The filename of the url log for a given key. -}
urlLogFile :: Key -> FilePath
diff --git a/Logs/MapLog.hs b/Logs/MapLog.hs
index 1725ef953..dd3cc0696 100644
--- a/Logs/MapLog.hs
+++ b/Logs/MapLog.hs
@@ -15,7 +15,7 @@ import qualified Data.Map as M
import Data.Time.Clock.POSIX
import Data.Time
import System.Locale
-
+
import Common
data TimeStamp = Unknown | Date POSIXTime
diff --git a/Logs/SingleValue.hs b/Logs/SingleValue.hs
index cbebdc8e5..bb774b6f4 100644
--- a/Logs/SingleValue.hs
+++ b/Logs/SingleValue.hs
@@ -60,6 +60,6 @@ getLog = newestValue <$$> readLog
setLog :: (SingleValueSerializable v) => FilePath -> v -> Annex ()
setLog f v = do
- now <- liftIO getPOSIXTime
- let ent = LogEntry now v
+ now <- liftIO getPOSIXTime
+ let ent = LogEntry now v
Annex.Branch.change f $ \_old -> showLog (S.singleton ent)
diff --git a/Remote/Helper/Encryptable.hs b/Remote/Helper/Encryptable.hs
index 05f3fc3f9..9a8e9ba5b 100644
--- a/Remote/Helper/Encryptable.hs
+++ b/Remote/Helper/Encryptable.hs
@@ -58,7 +58,7 @@ encryptionSetup c = maybe genCipher updateCipher $ extractCipher c
Just "shared" -> use "encryption setup" . genSharedCipher
=<< highRandomQuality
-- hybrid encryption is the default when a keyid is
- -- specified but no encryption
+ -- specified but no encryption
_ | maybe (M.member "keyid" c) (== "hybrid") encryption ->
use "encryption setup" . genEncryptedCipher key Hybrid
=<< highRandomQuality
@@ -88,10 +88,10 @@ encryptionSetup c = maybe genCipher updateCipher $ extractCipher c
(&&) (maybe True ( /= "false") $ M.lookup "highRandomQuality" c)
<$> fmap not (Annex.getState Annex.fast)
c' = foldr M.delete c
- -- git-annex used to remove 'encryption' as well, since
- -- it was redundant; we now need to keep it for
- -- public-key encryption, hence we leave it on newer
- -- remotes (while being backward-compatible).
+ -- git-annex used to remove 'encryption' as well, since
+ -- it was redundant; we now need to keep it for
+ -- public-key encryption, hence we leave it on newer
+ -- remotes (while being backward-compatible).
[ "keyid", "keyid+", "keyid-", "highRandomQuality" ]
remoteCipher :: RemoteConfig -> Annex (Maybe Cipher)
diff --git a/Remote/Helper/Special.hs b/Remote/Helper/Special.hs
index 5b9db9b08..4738180a8 100644
--- a/Remote/Helper/Special.hs
+++ b/Remote/Helper/Special.hs
@@ -87,7 +87,7 @@ checkPrepare checker helper k a = ifM (checker k)
-- Use to acquire a resource when preparing a helper.
resourcePrepare :: (Key -> (r -> Annex Bool) -> Annex Bool) -> (r -> helper) -> Preparer helper
resourcePrepare withr helper k a = withr k $ \r ->
- a (Just (helper r))
+ a (Just (helper r))
-- A Storer that expects to be provided with a file containing
-- the content of the key to store.
diff --git a/RemoteDaemon/Types.hs b/RemoteDaemon/Types.hs
index 0a7269534..7413f5851 100644
--- a/RemoteDaemon/Types.hs
+++ b/RemoteDaemon/Types.hs
@@ -20,7 +20,7 @@ import Control.Concurrent
-- The URI of a remote is used to uniquely identify it (names change..)
newtype RemoteURI = RemoteURI URI
- deriving (Show)
+ deriving (Show)
-- A Transport for a particular git remote consumes some messages
-- from a Chan, and emits others to another Chan.
diff --git a/Test.hs b/Test.hs
index 50d2f1d55..1c9bf4e6a 100644
--- a/Test.hs
+++ b/Test.hs
@@ -943,12 +943,12 @@ test_remove_conflict_resolution testenv = do
length v == 1
@? (what ++ " too many variant files in: " ++ show v)
- {- Check merge confalict resolution when a file is annexed in one repo,
- - and checked directly into git in the other repo.
- -
- - This test requires indirect mode to set it up, but tests both direct and
- - indirect mode.
- -}
+{- Check merge confalict resolution when a file is annexed in one repo,
+ - and checked directly into git in the other repo.
+ -
+ - This test requires indirect mode to set it up, but tests both direct and
+ - indirect mode.
+ -}
test_nonannexed_file_conflict_resolution :: TestEnv -> Assertion
test_nonannexed_file_conflict_resolution testenv = do
check True False
diff --git a/Types/Crypto.hs b/Types/Crypto.hs
index 1a9a7774a..48d03ce12 100644
--- a/Types/Crypto.hs
+++ b/Types/Crypto.hs
@@ -59,10 +59,10 @@ readMac "HMACSHA512" = Just HmacSha512
readMac _ = Nothing
calcMac
- :: Mac -- ^ MAC
- -> L.ByteString -- ^ secret key
- -> L.ByteString -- ^ message
- -> String -- ^ MAC'ed message, in hexadecimals
+ :: Mac -- ^ MAC
+ -> L.ByteString -- ^ secret key
+ -> L.ByteString -- ^ message
+ -> String -- ^ MAC'ed message, in hexadecimal
calcMac mac = case mac of
HmacSha1 -> showDigest $* hmacSha1
HmacSha224 -> showDigest $* hmacSha224
diff --git a/Types/ScheduledActivity.hs b/Types/ScheduledActivity.hs
index b683409ce..5cdbe29e8 100644
--- a/Types/ScheduledActivity.hs
+++ b/Types/ScheduledActivity.hs
@@ -17,7 +17,7 @@ import Data.Either
data ScheduledActivity
= ScheduledSelfFsck Schedule Duration
| ScheduledRemoteFsck UUID Schedule Duration
- deriving (Eq, Read, Show, Ord)
+ deriving (Eq, Read, Show, Ord)
{- Activities that run on a remote, within a time window, so
- should be run when the remote gets connected. -}
diff --git a/Utility/HumanTime.hs b/Utility/HumanTime.hs
index 4214ea680..3c23f31f7 100644
--- a/Utility/HumanTime.hs
+++ b/Utility/HumanTime.hs
@@ -27,7 +27,7 @@ import Control.Applicative
import qualified Data.Map as M
newtype Duration = Duration { durationSeconds :: Integer }
- deriving (Eq, Ord, Read, Show)
+ deriving (Eq, Ord, Read, Show)
durationSince :: UTCTime -> IO Duration
durationSince pasttime = do
diff --git a/Utility/Scheduled.hs b/Utility/Scheduled.hs
index 5a14b15f3..4fa3a29f1 100644
--- a/Utility/Scheduled.hs
+++ b/Utility/Scheduled.hs
@@ -44,7 +44,7 @@ import Data.Char
{- Some sort of scheduled event. -}
data Schedule = Schedule Recurrance ScheduledTime
- deriving (Eq, Read, Show, Ord)
+ deriving (Eq, Read, Show, Ord)
data Recurrance
= Daily
@@ -54,7 +54,7 @@ data Recurrance
| Divisible Int Recurrance
-- ^ Days, Weeks, or Months of the year evenly divisible by a number.
-- (Divisible Year is years evenly divisible by a number.)
- deriving (Eq, Read, Show, Ord)
+ deriving (Eq, Read, Show, Ord)
type WeekDay = Int
type MonthDay = Int
@@ -63,7 +63,7 @@ type YearDay = Int
data ScheduledTime
= AnyTime
| SpecificTime Hour Minute
- deriving (Eq, Read, Show, Ord)
+ deriving (Eq, Read, Show, Ord)
type Hour = Int
type Minute = Int
@@ -73,7 +73,7 @@ type Minute = Int
data NextTime
= NextTimeExactly LocalTime
| NextTimeWindow LocalTime LocalTime
- deriving (Eq, Read, Show)
+ deriving (Eq, Read, Show)
startTime :: NextTime -> LocalTime
startTime (NextTimeExactly t) = t