Add missing top-level type signatures

Add `-Wmissing-signatures` to `ghc-options`.
This commit is contained in:
Erik de Castro Lopo 2018-08-29 20:22:54 +10:00
parent ca56a29d78
commit df39a6d235
11 changed files with 65 additions and 22 deletions

View File

@ -49,7 +49,7 @@ data-files:
library
hs-source-dirs: src
default-language: Haskell2010
ghc-options: -Wincomplete-patterns
ghc-options: -Wincomplete-patterns -Wmissing-signatures
build-depends:
aeson >=1.0,
base >=4.9,
@ -125,7 +125,7 @@ executable ihaskell
-- Other library packages from which modules are imported.
default-language: Haskell2010
ghc-options: -Wincomplete-patterns
ghc-options: -Wincomplete-patterns -Wmissing-signatures
build-depends:
ihaskell -any,
base >=4.9 && < 4.13,
@ -152,7 +152,7 @@ Test-Suite hspec
IHaskell.Test.Util
IHaskell.Test.Parser
default-language: Haskell2010
ghc-options: -Wincomplete-patterns
ghc-options: -Wincomplete-patterns -Wmissing-signatures
build-depends:
base,
ihaskell,

View File

@ -1,4 +1,5 @@
{-# language NoImplicitPrelude, DoAndIfThenElse, OverloadedStrings, ExtendedDefaultRules #-}{-# LANGUAGE CPP #-}
{-# language NoImplicitPrelude, DoAndIfThenElse, OverloadedStrings, ExtendedDefaultRules #-}
{-# LANGUAGE CPP #-}
module IHaskellPrelude (
module IHaskellPrelude,
module X,
@ -64,7 +65,8 @@ module IHaskellPrelude (
import Prelude
import Data.Monoid as X
import Data.Semigroup as X
import Data.Monoid as X hiding ((<>), First(..), Last(..))
import Data.Tuple as X
import Control.Monad as X
import Data.Maybe as X
@ -83,7 +85,7 @@ import Data.List as X hiding (head, last, tail, init, tra
elemIndices, elemIndex, findIndex, findIndices, zip5, zip6,
zip7, zipWith5, zipWith6, zipWith7, unzip5, unzip6, unzip6,
delete, union, lookup, intersect, insert, deleteBy,
deleteFirstBy, unionBy, intersectBy, group, groupBy, insertBy,
unionBy, intersectBy, group, groupBy, insertBy,
maximumBy, minimumBy, genericLength, genericDrop, genericTake,
genericSplitAt, genericIndex, genericReplicate, inits, tails)
@ -111,13 +113,27 @@ type LByteString = Data.ByteString.Lazy.ByteString
type LText = Data.Text.Lazy.Text
(headMay, tailMay, lastMay, initMay, maximumMay, minimumMay) =
(wrapEmpty head, wrapEmpty tail, wrapEmpty last,
wrapEmpty init, wrapEmpty maximum, wrapEmpty minimum)
where
wrapEmpty :: ([a] -> b) -> [a] -> Maybe b
wrapEmpty _ [] = Nothing
wrapEmpty f xs = Just (f xs)
headMay :: [a] -> Maybe a
headMay = wrapEmpty head
tailMay :: [a] -> Maybe [a]
tailMay = wrapEmpty tail
lastMay :: [a] -> Maybe a
lastMay = wrapEmpty last
initMay :: [a] -> Maybe [a]
initMay = wrapEmpty init
maximumMay :: Ord a => [a] -> Maybe a
maximumMay = wrapEmpty maximum
minimumMay :: Ord a => [a] -> Maybe a
minimumMay = wrapEmpty minimum
wrapEmpty :: ([a] -> b) -> [a] -> Maybe b
wrapEmpty _ [] = Nothing
wrapEmpty f xs = Just (f xs)
maximumByMay :: (a -> a -> Ordering) -> [a] -> Maybe a
maximumByMay _ [] = Nothing

View File

@ -201,6 +201,7 @@ printDisplay disp = display disp >>= atomically . writeTChan displayChan
-- | Convenience function for client libraries. Switch to a temporary directory so that any files we
-- create aren't visible. On Unix, this is usually /tmp.
switchToTmpDir :: IO ()
switchToTmpDir = void (try switchDir :: IO (Either SomeException ()))
where
switchDir =

View File

@ -69,6 +69,7 @@ exposedName :: (a, b) -> a
exposedName = fst
#endif
extName (FlagSpec { flagSpecName = name }) = name
extName (FlagSpec { flagSpecName = name }) = name
complete :: String -> Int -> Interpreter (String, [String])

View File

@ -1110,6 +1110,7 @@ doLoadModule name modName = do
return $ displayError $ "Failed to load module " ++ modName ++ ": " ++ show exception
objTarget :: DynFlags -> HscTarget
objTarget flags = defaultObjectTarget $ targetPlatform flags
keepingItVariable :: Interpreter a -> Interpreter a

View File

@ -28,6 +28,7 @@ manyTillEnd p end = scan
xs <- scan
return $ x : xs
manyTillEnd1 :: Parser a -> Parser [a] -> Parser [a]
manyTillEnd1 p end = do
x <- p
xs <- manyTillEnd p end
@ -39,15 +40,18 @@ unescapedChar p = try $ do
lookAhead p
return [x]
quotedString :: Parser [Char]
quotedString = do
quote <?> "expected starting quote"
(manyTillEnd anyChar (unescapedChar quote) <* quote) <?> "unexpected in quoted String "
unquotedString :: Parser [Char]
unquotedString = manyTillEnd1 anyChar end
where
end = unescapedChar space
<|> (lookAhead eol >> return [])
word :: Parser [Char]
word = quotedString <|> unquotedString <?> "word"
separator :: Parser String

View File

@ -139,6 +139,7 @@ pprDynFlags show_all dflags =
flgs1 = [Opt_PrintExplicitForalls]
flgs2 = [Opt_PrintExplicitKinds]
flgs3 :: [GeneralFlag]
flgs3 = [Opt_PrintBindResult, Opt_BreakOnException, Opt_BreakOnError, Opt_PrintEvldWithShow]
-- | Pretty-print the base language and active options (taken from `InteractiveUI` module of

View File

@ -132,8 +132,10 @@ installPrefixFlag :: Flag Args
installPrefixFlag = flagReq ["prefix"] (store KernelspecInstallPrefix) "<install-dir>"
"Installation prefix for kernelspec (see Jupyter's --prefix option)"
helpFlag :: Flag Args
helpFlag = flagHelpSimple (add Help)
add :: Argument -> Args -> Args
add flag (Args mode flags) = Args mode $ flag : flags
store :: (String -> Argument) -> String -> Args -> Either String Args
@ -204,6 +206,7 @@ ihaskellArgs =
where
add flag (Args mode flags) = Args mode $ flag : flags
noArgs :: Arg a
noArgs = flagArg unexpected ""
where
unexpected a = error $ "Unexpected argument: " ++ a

View File

@ -106,6 +106,7 @@ ipython suppress args = do
else return ""
-- | Run while suppressing all output.
quietRun :: SH.FilePath -> [Text] -> SH.Sh ()
quietRun path args = SH.runHandles path args handles nothing
where
handles = [SH.InHandle SH.Inherit, SH.OutHandle SH.CreatePipe, SH.ErrorHandle SH.CreatePipe]

View File

@ -85,7 +85,7 @@ import Data.List as X hiding (head, last, tail, init, tra
elemIndices, elemIndex, findIndex, findIndices, zip5, zip6,
zip7, zipWith5, zipWith6, zipWith7, unzip5, unzip6, unzip6,
delete, union, lookup, intersect, insert, deleteBy,
deleteFirstBy, unionBy, intersectBy, group, groupBy, insertBy,
unionBy, intersectBy, group, groupBy, insertBy,
maximumBy, minimumBy, genericLength, genericDrop, genericTake,
genericSplitAt, genericIndex, genericReplicate, inits, tails)
@ -113,13 +113,27 @@ type LByteString = Data.ByteString.Lazy.ByteString
type LText = Data.Text.Lazy.Text
(headMay, tailMay, lastMay, initMay, maximumMay, minimumMay) =
(wrapEmpty head, wrapEmpty tail, wrapEmpty last,
wrapEmpty init, wrapEmpty maximum, wrapEmpty minimum)
where
wrapEmpty :: ([a] -> b) -> [a] -> Maybe b
wrapEmpty _ [] = Nothing
wrapEmpty f xs = Just (f xs)
headMay :: [a] -> Maybe a
headMay = wrapEmpty head
tailMay :: [a] -> Maybe [a]
tailMay = wrapEmpty tail
lastMay :: [a] -> Maybe a
lastMay = wrapEmpty last
initMay :: [a] -> Maybe [a]
initMay = wrapEmpty init
maximumMay :: Ord a => [a] -> Maybe a
maximumMay = wrapEmpty maximum
minimumMay :: Ord a => [a] -> Maybe a
minimumMay = wrapEmpty minimum
wrapEmpty :: ([a] -> b) -> [a] -> Maybe b
wrapEmpty _ [] = Nothing
wrapEmpty f xs = Just (f xs)
maximumByMay :: (a -> a -> Ordering) -> [a] -> Maybe a
maximumByMay _ [] = Nothing

View File

@ -48,6 +48,7 @@ shouldHaveCompletionsInDirectory string expected = do
unmatched = filter (not . existsInCompletion) expected
expected `shouldBeAmong` completions
completionHas :: String -> [String] -> IO ()
completionHas string expected = do
(matched, completions) <- ghc $ do
initCompleter