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.
This commit is contained in:
Joey Hess 2014-10-09 15:09:26 -04:00
parent 7b50b3c057
commit 9fd95d9025
19 changed files with 49 additions and 49 deletions

View file

@ -49,13 +49,13 @@ fromTaggedBranch b = case split "/" $ Git.fromRef b of
taggedPush :: UUID -> Maybe String -> Git.Ref -> Remote -> Git.Repo -> IO Bool taggedPush :: UUID -> Maybe String -> Git.Ref -> Remote -> Git.Repo -> IO Bool
taggedPush u info branch remote = Git.Command.runBool taggedPush u info branch remote = Git.Command.runBool
[ Param "push" [ Param "push"
, Param $ Remote.name remote , Param $ Remote.name remote
{- Using forcePush here is safe because we "own" the tagged branch {- Using forcePush here is safe because we "own" the tagged branch
- we're pushing; it has no other writers. Ensures it is pushed - we're pushing; it has no other writers. Ensures it is pushed
- even if it has been rewritten by a transition. -} - even if it has been rewritten by a transition. -}
, Param $ Git.Branch.forcePush $ refspec Annex.Branch.name , Param $ Git.Branch.forcePush $ refspec Annex.Branch.name
, Param $ refspec branch , Param $ refspec branch
] ]
where where
refspec b = Git.fromRef b ++ ":" ++ Git.fromRef (toTaggedBranch u info b) refspec b = Git.fromRef b ++ ":" ++ Git.fromRef (toTaggedBranch u info b)

View file

@ -72,7 +72,7 @@ needLsof = error $ unlines
{- A special exception that can be thrown to pause or resume the watcher. -} {- A special exception that can be thrown to pause or resume the watcher. -}
data WatcherControl = PauseWatcher | ResumeWatcher data WatcherControl = PauseWatcher | ResumeWatcher
deriving (Show, Eq, Typeable) deriving (Show, Eq, Typeable)
instance E.Exception WatcherControl instance E.Exception WatcherControl

View file

@ -101,8 +101,8 @@ itemNameHelp = [whamlet|
iaCredsAForm :: Maybe CredPair -> MkAForm AWS.AWSCreds iaCredsAForm :: Maybe CredPair -> MkAForm AWS.AWSCreds
iaCredsAForm defcreds = AWS.AWSCreds iaCredsAForm defcreds = AWS.AWSCreds
<$> accessKeyIDFieldWithHelp (T.pack . fst <$> defcreds) <$> accessKeyIDFieldWithHelp (T.pack . fst <$> defcreds)
<*> AWS.secretAccessKeyField (T.pack . snd <$> defcreds) <*> AWS.secretAccessKeyField (T.pack . snd <$> defcreds)
#ifdef WITH_S3 #ifdef WITH_S3
previouslyUsedIACreds :: Annex (Maybe CredPair) previouslyUsedIACreds :: Annex (Maybe CredPair)

View file

@ -16,7 +16,7 @@ import qualified Remote
data RepoId data RepoId
= RepoUUID UUID = RepoUUID UUID
| RepoName RemoteName | RepoName RemoteName
deriving (Eq, Ord, Show, Read) deriving (Eq, Ord, Show, Read)
mkRepoId :: Remote -> RepoId mkRepoId :: Remote -> RepoId
mkRepoId r = case Remote.uuid r of mkRepoId r = case Remote.uuid r of

View file

@ -40,7 +40,7 @@ main :: IO ()
main = getArgs >>= go main = getArgs >>= go
where where
go [] = error "specify topdir" go [] = error "specify topdir"
go (topdir:_) = do go (topdir:_) = do
let dir = progDir topdir let dir = progDir topdir
createDirectoryIfMissing True dir createDirectoryIfMissing True dir
installed <- forM bundledPrograms $ installProg dir installed <- forM bundledPrograms $ installProg dir

View file

@ -282,7 +282,7 @@ verifyDirectMode key file = do
- the key's metadata, if available. - the key's metadata, if available.
- -
- Not checked in direct mode, because files can be changed directly. - Not checked in direct mode, because files can be changed directly.
-} -}
checkKeySize :: Key -> Annex Bool checkKeySize :: Key -> Annex Bool
checkKeySize key = ifM isDirect checkKeySize key = ifM isDirect
( return True ( return True

View file

@ -71,15 +71,15 @@ type Present = Bool
header :: [(RemoteName, TrustLevel)] -> String header :: [(RemoteName, TrustLevel)] -> String
header remotes = unlines (zipWith formatheader [0..] remotes) ++ pipes (length remotes) header remotes = unlines (zipWith formatheader [0..] remotes) ++ pipes (length remotes)
where where
formatheader n (remotename, trustlevel) = pipes n ++ remotename ++ trust trustlevel formatheader n (remotename, trustlevel) = pipes n ++ remotename ++ trust trustlevel
pipes = flip replicate '|' pipes = flip replicate '|'
trust UnTrusted = " (untrusted)" trust UnTrusted = " (untrusted)"
trust _ = "" trust _ = ""
format :: [(TrustLevel, Present)] -> FilePath -> String format :: [(TrustLevel, Present)] -> FilePath -> String
format remotes file = thereMap ++ " " ++ file format remotes file = thereMap ++ " " ++ file
where where
thereMap = concatMap there remotes thereMap = concatMap there remotes
there (UnTrusted, True) = "x" there (UnTrusted, True) = "x"
there (_, True) = "X" there (_, True) = "X"
there (_, False) = "_" there (_, False) = "_"

View file

@ -53,7 +53,7 @@ diffIndex ref = diffIndex' ref [Param "--cached"]
diffWorkTree :: Ref -> Repo -> IO ([DiffTreeItem], IO Bool) diffWorkTree :: Ref -> Repo -> IO ([DiffTreeItem], IO Bool)
diffWorkTree ref repo = diffWorkTree ref repo =
ifM (Git.Ref.headExists repo) ifM (Git.Ref.headExists repo)
( diffIndex' ref [] repo ( diffIndex' ref [] repo
, return ([], return True) , return ([], return True)
) )

View file

@ -90,11 +90,11 @@ locationLogFile key = hashDirLower key ++ keyFile key ++ ".log"
locationLogFileKey :: FilePath -> Maybe Key locationLogFileKey :: FilePath -> Maybe Key
locationLogFileKey path locationLogFileKey path
| ["remote", "web"] `isPrefixOf` splitDirectories dir = Nothing | ["remote", "web"] `isPrefixOf` splitDirectories dir = Nothing
| ext == ".log" = fileKey base | ext == ".log" = fileKey base
| otherwise = Nothing | otherwise = Nothing
where where
(dir, file) = splitFileName path (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. -} {- The filename of the url log for a given key. -}
urlLogFile :: Key -> FilePath urlLogFile :: Key -> FilePath

View file

@ -15,7 +15,7 @@ import qualified Data.Map as M
import Data.Time.Clock.POSIX import Data.Time.Clock.POSIX
import Data.Time import Data.Time
import System.Locale import System.Locale
import Common import Common
data TimeStamp = Unknown | Date POSIXTime data TimeStamp = Unknown | Date POSIXTime

View file

@ -60,6 +60,6 @@ getLog = newestValue <$$> readLog
setLog :: (SingleValueSerializable v) => FilePath -> v -> Annex () setLog :: (SingleValueSerializable v) => FilePath -> v -> Annex ()
setLog f v = do setLog f v = do
now <- liftIO getPOSIXTime now <- liftIO getPOSIXTime
let ent = LogEntry now v let ent = LogEntry now v
Annex.Branch.change f $ \_old -> showLog (S.singleton ent) Annex.Branch.change f $ \_old -> showLog (S.singleton ent)

View file

@ -58,7 +58,7 @@ encryptionSetup c = maybe genCipher updateCipher $ extractCipher c
Just "shared" -> use "encryption setup" . genSharedCipher Just "shared" -> use "encryption setup" . genSharedCipher
=<< highRandomQuality =<< highRandomQuality
-- hybrid encryption is the default when a keyid is -- hybrid encryption is the default when a keyid is
-- specified but no encryption -- specified but no encryption
_ | maybe (M.member "keyid" c) (== "hybrid") encryption -> _ | maybe (M.member "keyid" c) (== "hybrid") encryption ->
use "encryption setup" . genEncryptedCipher key Hybrid use "encryption setup" . genEncryptedCipher key Hybrid
=<< highRandomQuality =<< highRandomQuality
@ -88,10 +88,10 @@ encryptionSetup c = maybe genCipher updateCipher $ extractCipher c
(&&) (maybe True ( /= "false") $ M.lookup "highRandomQuality" c) (&&) (maybe True ( /= "false") $ M.lookup "highRandomQuality" c)
<$> fmap not (Annex.getState Annex.fast) <$> fmap not (Annex.getState Annex.fast)
c' = foldr M.delete c c' = foldr M.delete c
-- git-annex used to remove 'encryption' as well, since -- git-annex used to remove 'encryption' as well, since
-- it was redundant; we now need to keep it for -- it was redundant; we now need to keep it for
-- public-key encryption, hence we leave it on newer -- public-key encryption, hence we leave it on newer
-- remotes (while being backward-compatible). -- remotes (while being backward-compatible).
[ "keyid", "keyid+", "keyid-", "highRandomQuality" ] [ "keyid", "keyid+", "keyid-", "highRandomQuality" ]
remoteCipher :: RemoteConfig -> Annex (Maybe Cipher) remoteCipher :: RemoteConfig -> Annex (Maybe Cipher)

View file

@ -87,7 +87,7 @@ checkPrepare checker helper k a = ifM (checker k)
-- Use to acquire a resource when preparing a helper. -- Use to acquire a resource when preparing a helper.
resourcePrepare :: (Key -> (r -> Annex Bool) -> Annex Bool) -> (r -> helper) -> Preparer helper resourcePrepare :: (Key -> (r -> Annex Bool) -> Annex Bool) -> (r -> helper) -> Preparer helper
resourcePrepare withr helper k a = withr k $ \r -> 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 -- A Storer that expects to be provided with a file containing
-- the content of the key to store. -- the content of the key to store.

View file

@ -20,7 +20,7 @@ import Control.Concurrent
-- The URI of a remote is used to uniquely identify it (names change..) -- The URI of a remote is used to uniquely identify it (names change..)
newtype RemoteURI = RemoteURI URI newtype RemoteURI = RemoteURI URI
deriving (Show) deriving (Show)
-- A Transport for a particular git remote consumes some messages -- A Transport for a particular git remote consumes some messages
-- from a Chan, and emits others to another Chan. -- from a Chan, and emits others to another Chan.

12
Test.hs
View file

@ -943,12 +943,12 @@ test_remove_conflict_resolution testenv = do
length v == 1 length v == 1
@? (what ++ " too many variant files in: " ++ show v) @? (what ++ " too many variant files in: " ++ show v)
{- Check merge confalict resolution when a file is annexed in one repo, {- Check merge confalict resolution when a file is annexed in one repo,
- and checked directly into git in the other repo. - and checked directly into git in the other repo.
- -
- This test requires indirect mode to set it up, but tests both direct and - This test requires indirect mode to set it up, but tests both direct and
- indirect mode. - indirect mode.
-} -}
test_nonannexed_file_conflict_resolution :: TestEnv -> Assertion test_nonannexed_file_conflict_resolution :: TestEnv -> Assertion
test_nonannexed_file_conflict_resolution testenv = do test_nonannexed_file_conflict_resolution testenv = do
check True False check True False

View file

@ -59,10 +59,10 @@ readMac "HMACSHA512" = Just HmacSha512
readMac _ = Nothing readMac _ = Nothing
calcMac calcMac
:: Mac -- ^ MAC :: Mac -- ^ MAC
-> L.ByteString -- ^ secret key -> L.ByteString -- ^ secret key
-> L.ByteString -- ^ message -> L.ByteString -- ^ message
-> String -- ^ MAC'ed message, in hexadecimals -> String -- ^ MAC'ed message, in hexadecimal
calcMac mac = case mac of calcMac mac = case mac of
HmacSha1 -> showDigest $* hmacSha1 HmacSha1 -> showDigest $* hmacSha1
HmacSha224 -> showDigest $* hmacSha224 HmacSha224 -> showDigest $* hmacSha224

View file

@ -17,7 +17,7 @@ import Data.Either
data ScheduledActivity data ScheduledActivity
= ScheduledSelfFsck Schedule Duration = ScheduledSelfFsck Schedule Duration
| ScheduledRemoteFsck UUID 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 {- Activities that run on a remote, within a time window, so
- should be run when the remote gets connected. -} - should be run when the remote gets connected. -}

View file

@ -27,7 +27,7 @@ import Control.Applicative
import qualified Data.Map as M import qualified Data.Map as M
newtype Duration = Duration { durationSeconds :: Integer } newtype Duration = Duration { durationSeconds :: Integer }
deriving (Eq, Ord, Read, Show) deriving (Eq, Ord, Read, Show)
durationSince :: UTCTime -> IO Duration durationSince :: UTCTime -> IO Duration
durationSince pasttime = do durationSince pasttime = do

View file

@ -44,7 +44,7 @@ import Data.Char
{- Some sort of scheduled event. -} {- Some sort of scheduled event. -}
data Schedule = Schedule Recurrance ScheduledTime data Schedule = Schedule Recurrance ScheduledTime
deriving (Eq, Read, Show, Ord) deriving (Eq, Read, Show, Ord)
data Recurrance data Recurrance
= Daily = Daily
@ -54,7 +54,7 @@ data Recurrance
| Divisible Int Recurrance | Divisible Int Recurrance
-- ^ Days, Weeks, or Months of the year evenly divisible by a number. -- ^ Days, Weeks, or Months of the year evenly divisible by a number.
-- (Divisible Year is years 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 WeekDay = Int
type MonthDay = Int type MonthDay = Int
@ -63,7 +63,7 @@ type YearDay = Int
data ScheduledTime data ScheduledTime
= AnyTime = AnyTime
| SpecificTime Hour Minute | SpecificTime Hour Minute
deriving (Eq, Read, Show, Ord) deriving (Eq, Read, Show, Ord)
type Hour = Int type Hour = Int
type Minute = Int type Minute = Int
@ -73,7 +73,7 @@ type Minute = Int
data NextTime data NextTime
= NextTimeExactly LocalTime = NextTimeExactly LocalTime
| NextTimeWindow LocalTime LocalTime | NextTimeWindow LocalTime LocalTime
deriving (Eq, Read, Show) deriving (Eq, Read, Show)
startTime :: NextTime -> LocalTime startTime :: NextTime -> LocalTime
startTime (NextTimeExactly t) = t startTime (NextTimeExactly t) = t