fix some mixed space+tab indentation
This fixes all instances of " \t" in the code base. Most common case seems to be after a "where" line; probably vim copied the two space layout of that line. Done as a background task while listening to episode 2 of the Type Theory podcast.
This commit is contained in:
parent
8f69d55f03
commit
7b50b3c057
131 changed files with 242 additions and 242 deletions
|
@ -32,7 +32,7 @@ batch :: IO a -> IO a
|
|||
#if defined(linux_HOST_OS) || defined(__ANDROID__)
|
||||
batch a = wait =<< batchthread
|
||||
where
|
||||
batchthread = asyncBound $ do
|
||||
batchthread = asyncBound $ do
|
||||
setProcessPriority 0 maxNice
|
||||
a
|
||||
#else
|
||||
|
|
|
@ -65,7 +65,7 @@ query ch send receive = do
|
|||
restartable s (receive $ coProcessFrom s)
|
||||
return
|
||||
where
|
||||
restartable s a cont
|
||||
restartable s a cont
|
||||
| coProcessNumRestarts (coProcessSpec s) > 0 =
|
||||
maybe restart cont =<< catchMaybeIO a
|
||||
| otherwise = cont =<< a
|
||||
|
@ -87,7 +87,7 @@ rawMode ch = do
|
|||
raw $ coProcessTo s
|
||||
return ch
|
||||
where
|
||||
raw h = do
|
||||
raw h = do
|
||||
fileEncoding h
|
||||
#ifdef mingw32_HOST_OS
|
||||
hSetNewlineMode h noNewlineTranslation
|
||||
|
|
|
@ -47,10 +47,10 @@ createLinkOrCopy :: FilePath -> FilePath -> IO Bool
|
|||
#ifndef mingw32_HOST_OS
|
||||
createLinkOrCopy src dest = go `catchIO` const fallback
|
||||
where
|
||||
go = do
|
||||
go = do
|
||||
createLink src dest
|
||||
return True
|
||||
fallback = copyFileExternal CopyAllMetaData src dest
|
||||
fallback = copyFileExternal CopyAllMetaData src dest
|
||||
#else
|
||||
createLinkOrCopy = copyFileExternal CopyAllMetaData
|
||||
#endif
|
||||
|
|
|
@ -175,7 +175,7 @@ winLockFile pid pidfile = do
|
|||
cleanstale
|
||||
return $ prefix ++ show pid ++ suffix
|
||||
where
|
||||
prefix = pidfile ++ "."
|
||||
prefix = pidfile ++ "."
|
||||
suffix = ".lck"
|
||||
cleanstale = mapM_ (void . tryIO . removeFile) =<<
|
||||
(filter iswinlockfile <$> dirContents (parentDir pidfile))
|
||||
|
|
|
@ -120,7 +120,7 @@ roughSize units short i
|
|||
|
||||
showUnit x (Unit size abbrev name) = s ++ " " ++ unit
|
||||
where
|
||||
v = (fromInteger x :: Double) / fromInteger size
|
||||
v = (fromInteger x :: Double) / fromInteger size
|
||||
s = showImprecise 2 v
|
||||
unit
|
||||
| short = abbrev
|
||||
|
|
|
@ -56,7 +56,7 @@ dirContentsRecursive = dirContentsRecursiveSkipping (const False) True
|
|||
dirContentsRecursiveSkipping :: (FilePath -> Bool) -> Bool -> FilePath -> IO [FilePath]
|
||||
dirContentsRecursiveSkipping skipdir followsubdirsymlinks topdir = go [topdir]
|
||||
where
|
||||
go [] = return []
|
||||
go [] = return []
|
||||
go (dir:dirs)
|
||||
| skipdir (takeFileName dir) = go dirs
|
||||
| otherwise = unsafeInterleaveIO $ do
|
||||
|
@ -87,7 +87,7 @@ dirContentsRecursiveSkipping skipdir followsubdirsymlinks topdir = go [topdir]
|
|||
dirTreeRecursiveSkipping :: (FilePath -> Bool) -> FilePath -> IO [FilePath]
|
||||
dirTreeRecursiveSkipping skipdir topdir = go [] [topdir]
|
||||
where
|
||||
go c [] = return c
|
||||
go c [] = return c
|
||||
go c (dir:dirs)
|
||||
| skipdir (takeFileName dir) = go c dirs
|
||||
| otherwise = unsafeInterleaveIO $ do
|
||||
|
|
|
@ -57,7 +57,7 @@ externalSHA command shasize file = do
|
|||
Left $ "Unexpected character in output of " ++ command ++ "\"" ++ sha ++ "\""
|
||||
| otherwise = Right sha'
|
||||
where
|
||||
sha' = map toLower sha
|
||||
sha' = map toLower sha
|
||||
|
||||
expectedSHALength :: Int -> Int
|
||||
expectedSHALength 1 = 40
|
||||
|
|
|
@ -111,7 +111,7 @@ truncateFilePath :: Int -> FilePath -> FilePath
|
|||
#ifndef mingw32_HOST_OS
|
||||
truncateFilePath n = go . reverse
|
||||
where
|
||||
go f =
|
||||
go f =
|
||||
let bytes = decodeW8 f
|
||||
in if length bytes <= n
|
||||
then reverse f
|
||||
|
|
|
@ -117,7 +117,7 @@ decode_c s = unescape ("", s)
|
|||
handle (x:'x':n1:n2:rest)
|
||||
| isescape x && allhex = (fromhex, rest)
|
||||
where
|
||||
allhex = isHexDigit n1 && isHexDigit n2
|
||||
allhex = isHexDigit n1 && isHexDigit n2
|
||||
fromhex = [chr $ readhex [n1, n2]]
|
||||
readhex h = Prelude.read $ "0x" ++ h :: Int
|
||||
handle (x:n1:n2:n3:rest)
|
||||
|
|
|
@ -166,7 +166,7 @@ secretKeys :: IO (M.Map KeyId UserId)
|
|||
secretKeys = catchDefaultIO M.empty makemap
|
||||
where
|
||||
makemap = M.fromList . parse . lines <$> readStrict params
|
||||
params = [Params "--with-colons --list-secret-keys --fixed-list-mode"]
|
||||
params = [Params "--with-colons --list-secret-keys --fixed-list-mode"]
|
||||
parse = extract [] Nothing . map (split ":")
|
||||
extract c (Just keyid) (("uid":_:_:_:_:_:_:_:_:userid:_):rest) =
|
||||
extract ((keyid, decode_c userid):c) Nothing rest
|
||||
|
@ -196,7 +196,7 @@ genSecretKey keytype passphrase userid keysize =
|
|||
withHandle StdinHandle createProcessSuccess (proc gpgcmd params) feeder
|
||||
where
|
||||
params = ["--batch", "--gen-key"]
|
||||
feeder h = do
|
||||
feeder h = do
|
||||
hPutStr h $ unlines $ catMaybes
|
||||
[ Just $ "Key-Type: " ++
|
||||
case keytype of
|
||||
|
@ -232,7 +232,7 @@ genRandom highQuality size = checksize <$> readStrict
|
|||
randomquality :: Int
|
||||
randomquality = if highQuality then 2 else 1
|
||||
|
||||
{- The size is the number of bytes of entropy desired; the data is
|
||||
{- The size is the number of bytes of entropy desired; the data is
|
||||
- base64 encoded, so needs 8 bits to represent every 6 bytes of
|
||||
- entropy. -}
|
||||
expectedlength = size * 8 `div` 6
|
||||
|
|
|
@ -47,8 +47,8 @@ daysToDuration i = Duration $ i * dsecs
|
|||
parseDuration :: String -> Maybe Duration
|
||||
parseDuration = Duration <$$> go 0
|
||||
where
|
||||
go n [] = return n
|
||||
go n s = do
|
||||
go n [] = return n
|
||||
go n s = do
|
||||
num <- readish s :: Maybe Integer
|
||||
case dropWhile isDigit s of
|
||||
(c:rest) -> do
|
||||
|
|
|
@ -182,7 +182,7 @@ checkSentinalFile s = do
|
|||
SentinalStatus (not unchanged) tsdelta
|
||||
where
|
||||
#ifdef mingw32_HOST_OS
|
||||
unchanged = oldinode == newinode && oldsize == newsize
|
||||
unchanged = oldinode == newinode && oldsize == newsize
|
||||
tsdelta = TSDelta $ do
|
||||
-- Run when generating an InodeCache,
|
||||
-- to get the current delta.
|
||||
|
|
|
@ -90,7 +90,7 @@ tokenGroups :: [Token op] -> [TokenGroup op]
|
|||
tokenGroups [] = []
|
||||
tokenGroups (t:ts) = go t
|
||||
where
|
||||
go Open =
|
||||
go Open =
|
||||
let (gr, rest) = findClose ts
|
||||
in gr : tokenGroups rest
|
||||
go Close = tokenGroups ts -- not picky about missing Close
|
||||
|
@ -101,7 +101,7 @@ findClose l =
|
|||
let (g, rest) = go [] l
|
||||
in (Group (reverse g), rest)
|
||||
where
|
||||
go c [] = (c, []) -- not picky about extra Close
|
||||
go c [] = (c, []) -- not picky about extra Close
|
||||
go c (t:ts) = dispatch t
|
||||
where
|
||||
dispatch Close = (c, ts)
|
||||
|
|
|
@ -235,11 +235,11 @@ toCygPath p
|
|||
| null drive = recombine parts
|
||||
| otherwise = recombine $ "/cygdrive" : driveletter drive : parts
|
||||
where
|
||||
(drive, p') = splitDrive p
|
||||
(drive, p') = splitDrive p
|
||||
parts = splitDirectories p'
|
||||
driveletter = map toLower . takeWhile (/= ':')
|
||||
driveletter = map toLower . takeWhile (/= ':')
|
||||
recombine = fixtrailing . Posix.joinPath
|
||||
fixtrailing s
|
||||
fixtrailing s
|
||||
| hasTrailingPathSeparator p = Posix.addTrailingPathSeparator s
|
||||
| otherwise = s
|
||||
#endif
|
||||
|
@ -272,7 +272,7 @@ fileNameLengthLimit dir = do
|
|||
sanitizeFilePath :: String -> FilePath
|
||||
sanitizeFilePath = map sanitize
|
||||
where
|
||||
sanitize c
|
||||
sanitize c
|
||||
| c == '.' = c
|
||||
| isSpace c || isPunctuation c || isSymbol c || isControl c || c == '/' = '_'
|
||||
| otherwise = c
|
||||
|
|
|
@ -113,7 +113,7 @@ supported Quvi04 url = boolSystem "quvi"
|
|||
supported Quvi09 url = (firstlevel <&&> secondlevel)
|
||||
`catchNonAsync` (\_ -> return False)
|
||||
where
|
||||
firstlevel = case uriAuthority =<< parseURIRelaxed url of
|
||||
firstlevel = case uriAuthority =<< parseURIRelaxed url of
|
||||
Nothing -> return False
|
||||
Just auth -> do
|
||||
let domain = map toLower $ uriRegName auth
|
||||
|
|
|
@ -57,7 +57,7 @@ rsync = boolSystem "rsync" . rsyncParamsFixup
|
|||
rsyncParamsFixup :: [CommandParam] -> [CommandParam]
|
||||
rsyncParamsFixup = map fixup
|
||||
where
|
||||
fixup (File f) = File (toCygPath f)
|
||||
fixup (File f) = File (toCygPath f)
|
||||
fixup p = p
|
||||
|
||||
{- Runs rsync, but intercepts its progress output and updates a meter.
|
||||
|
|
|
@ -74,7 +74,7 @@ lookupSRV (SRV srv) = do
|
|||
maybe [] use r
|
||||
#endif
|
||||
where
|
||||
use = orderHosts . map tohosts
|
||||
use = orderHosts . map tohosts
|
||||
tohosts (priority, weight, port, hostname) =
|
||||
( (priority, weight)
|
||||
, (B8.toString hostname, PortNumber $ fromIntegral port)
|
||||
|
|
|
@ -96,9 +96,9 @@ calcNextTime schedule@(Schedule recurrance scheduledtime) lasttime currenttime
|
|||
NextTimeExactly t -> window (localDay t) (localDay t)
|
||||
| otherwise = NextTimeExactly . startTime <$> findfromtoday False
|
||||
where
|
||||
findfromtoday anytime = findfrom recurrance afterday today
|
||||
findfromtoday anytime = findfrom recurrance afterday today
|
||||
where
|
||||
today = localDay currenttime
|
||||
today = localDay currenttime
|
||||
afterday = sameaslastrun || toolatetoday
|
||||
toolatetoday = not anytime && localTimeOfDay currenttime >= nexttime
|
||||
sameaslastrun = lastrun == Just today
|
||||
|
@ -163,8 +163,8 @@ calcNextTime schedule@(Schedule recurrance scheduledtime) lasttime currenttime
|
|||
Divisible n r'@(Yearly _) -> handlediv n r' ynum Nothing
|
||||
Divisible _ r'@(Divisible _ _) -> findfrom r' afterday candidate
|
||||
where
|
||||
skip n = findfrom r False (addDays n candidate)
|
||||
handlediv n r' getval mmax
|
||||
skip n = findfrom r False (addDays n candidate)
|
||||
handlediv n r' getval mmax
|
||||
| n > 0 && maybe True (n <=) mmax =
|
||||
findfromwhere r' (divisible n . getval) afterday candidate
|
||||
| otherwise = Nothing
|
||||
|
@ -267,7 +267,7 @@ toRecurrance s = case words s of
|
|||
constructor u
|
||||
| "s" `isSuffixOf` u = constructor $ reverse $ drop 1 $ reverse u
|
||||
| otherwise = Nothing
|
||||
withday sd u = do
|
||||
withday sd u = do
|
||||
c <- constructor u
|
||||
d <- readish sd
|
||||
Just $ c (Just d)
|
||||
|
@ -285,7 +285,7 @@ fromScheduledTime AnyTime = "any time"
|
|||
fromScheduledTime (SpecificTime h m) =
|
||||
show h' ++ (if m > 0 then ":" ++ pad 2 (show m) else "") ++ " " ++ ampm
|
||||
where
|
||||
pad n s = take (n - length s) (repeat '0') ++ s
|
||||
pad n s = take (n - length s) (repeat '0') ++ s
|
||||
(h', ampm)
|
||||
| h == 0 = (12, "AM")
|
||||
| h < 12 = (h, "AM")
|
||||
|
@ -304,10 +304,10 @@ toScheduledTime v = case words v of
|
|||
(s:[]) -> go s id
|
||||
_ -> Nothing
|
||||
where
|
||||
h0 h
|
||||
h0 h
|
||||
| h == 12 = 0
|
||||
| otherwise = h
|
||||
go :: String -> (Int -> Int) -> Maybe ScheduledTime
|
||||
go :: String -> (Int -> Int) -> Maybe ScheduledTime
|
||||
go s adjust =
|
||||
let (h, m) = separate (== ':') s
|
||||
in SpecificTime
|
||||
|
@ -363,7 +363,7 @@ instance Arbitrary Recurrance where
|
|||
]
|
||||
]
|
||||
where
|
||||
arbday = oneof
|
||||
arbday = oneof
|
||||
[ Just <$> nonNegative arbitrary
|
||||
, pure Nothing
|
||||
]
|
||||
|
|
|
@ -56,7 +56,7 @@ parseSshConfig = go [] . lines
|
|||
| iscomment l = hoststanza host c ((Left $ mkcomment l):hc) ls
|
||||
| otherwise = case splitline l of
|
||||
(indent, k, v)
|
||||
| isHost k -> hoststanza v
|
||||
| isHost k -> hoststanza v
|
||||
(HostConfig host (reverse hc):c) [] ls
|
||||
| otherwise -> hoststanza host c
|
||||
((Right $ SshSetting indent k v):hc) ls
|
||||
|
@ -87,7 +87,7 @@ genSshConfig = unlines . concatMap gen
|
|||
findHostConfigKey :: SshConfig -> Key -> Maybe Value
|
||||
findHostConfigKey (HostConfig _ cs) wantk = go (rights cs) (map toLower wantk)
|
||||
where
|
||||
go [] _ = Nothing
|
||||
go [] _ = Nothing
|
||||
go ((SshSetting _ k v):rest) wantk'
|
||||
| map toLower k == wantk' = Just v
|
||||
| otherwise = go rest wantk'
|
||||
|
@ -98,7 +98,7 @@ addToHostConfig :: SshConfig -> Key -> Value -> SshConfig
|
|||
addToHostConfig (HostConfig host cs) k v =
|
||||
HostConfig host $ Right (SshSetting indent k v) : cs
|
||||
where
|
||||
{- The indent is taken from any existing SshSetting
|
||||
{- The indent is taken from any existing SshSetting
|
||||
- in the HostConfig (largest indent wins). -}
|
||||
indent = fromMaybe "\t" $ headMaybe $ reverse $
|
||||
sortBy (comparing length) $ map getindent cs
|
||||
|
|
|
@ -57,7 +57,7 @@ modifyTList tlist a = do
|
|||
unless (emptyDList dl') $
|
||||
putTMVar tlist dl'
|
||||
where
|
||||
emptyDList = D.list True (\_ _ -> False)
|
||||
emptyDList = D.list True (\_ _ -> False)
|
||||
|
||||
consTList :: TList a -> a -> STM ()
|
||||
consTList tlist v = modifyTList tlist $ \dl -> D.cons v dl
|
||||
|
|
|
@ -117,7 +117,7 @@ getSocket h = do
|
|||
when (isJust h) $
|
||||
error "getSocket with HostName not supported on this OS"
|
||||
addr <- inet_addr "127.0.0.1"
|
||||
sock <- socket AF_INET Stream defaultProtocol
|
||||
sock <- socket AF_INET Stream defaultProtocol
|
||||
preparesocket sock
|
||||
bindSocket sock (SockAddrInet aNY_PORT addr)
|
||||
use sock
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue