Commit df39a6d2 authored by Erik de Castro Lopo's avatar Erik de Castro Lopo

Add missing top-level type signatures

Add `-Wmissing-signatures` to `ghc-options`.
parent ca56a29d
...@@ -49,7 +49,7 @@ data-files: ...@@ -49,7 +49,7 @@ data-files:
library library
hs-source-dirs: src hs-source-dirs: src
default-language: Haskell2010 default-language: Haskell2010
ghc-options: -Wincomplete-patterns ghc-options: -Wincomplete-patterns -Wmissing-signatures
build-depends: build-depends:
aeson >=1.0, aeson >=1.0,
base >=4.9, base >=4.9,
...@@ -125,7 +125,7 @@ executable ihaskell ...@@ -125,7 +125,7 @@ executable ihaskell
-- Other library packages from which modules are imported. -- Other library packages from which modules are imported.
default-language: Haskell2010 default-language: Haskell2010
ghc-options: -Wincomplete-patterns ghc-options: -Wincomplete-patterns -Wmissing-signatures
build-depends: build-depends:
ihaskell -any, ihaskell -any,
base >=4.9 && < 4.13, base >=4.9 && < 4.13,
...@@ -152,7 +152,7 @@ Test-Suite hspec ...@@ -152,7 +152,7 @@ Test-Suite hspec
IHaskell.Test.Util IHaskell.Test.Util
IHaskell.Test.Parser IHaskell.Test.Parser
default-language: Haskell2010 default-language: Haskell2010
ghc-options: -Wincomplete-patterns ghc-options: -Wincomplete-patterns -Wmissing-signatures
build-depends: build-depends:
base, base,
ihaskell, ihaskell,
......
{-# language NoImplicitPrelude, DoAndIfThenElse, OverloadedStrings, ExtendedDefaultRules #-}{-# LANGUAGE CPP #-} {-# language NoImplicitPrelude, DoAndIfThenElse, OverloadedStrings, ExtendedDefaultRules #-}
{-# LANGUAGE CPP #-}
module IHaskellPrelude ( module IHaskellPrelude (
module IHaskellPrelude, module IHaskellPrelude,
module X, module X,
...@@ -64,7 +65,8 @@ module IHaskellPrelude ( ...@@ -64,7 +65,8 @@ module IHaskellPrelude (
import Prelude 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 Data.Tuple as X
import Control.Monad as X import Control.Monad as X
import Data.Maybe as X import Data.Maybe as X
...@@ -83,7 +85,7 @@ import Data.List as X hiding (head, last, tail, init, tra ...@@ -83,7 +85,7 @@ import Data.List as X hiding (head, last, tail, init, tra
elemIndices, elemIndex, findIndex, findIndices, zip5, zip6, elemIndices, elemIndex, findIndex, findIndices, zip5, zip6,
zip7, zipWith5, zipWith6, zipWith7, unzip5, unzip6, unzip6, zip7, zipWith5, zipWith6, zipWith7, unzip5, unzip6, unzip6,
delete, union, lookup, intersect, insert, deleteBy, delete, union, lookup, intersect, insert, deleteBy,
deleteFirstBy, unionBy, intersectBy, group, groupBy, insertBy, unionBy, intersectBy, group, groupBy, insertBy,
maximumBy, minimumBy, genericLength, genericDrop, genericTake, maximumBy, minimumBy, genericLength, genericDrop, genericTake,
genericSplitAt, genericIndex, genericReplicate, inits, tails) genericSplitAt, genericIndex, genericReplicate, inits, tails)
...@@ -111,13 +113,27 @@ type LByteString = Data.ByteString.Lazy.ByteString ...@@ -111,13 +113,27 @@ type LByteString = Data.ByteString.Lazy.ByteString
type LText = Data.Text.Lazy.Text type LText = Data.Text.Lazy.Text
(headMay, tailMay, lastMay, initMay, maximumMay, minimumMay) = headMay :: [a] -> Maybe a
(wrapEmpty head, wrapEmpty tail, wrapEmpty last, headMay = wrapEmpty head
wrapEmpty init, wrapEmpty maximum, wrapEmpty minimum)
where tailMay :: [a] -> Maybe [a]
wrapEmpty :: ([a] -> b) -> [a] -> Maybe b tailMay = wrapEmpty tail
wrapEmpty _ [] = Nothing
wrapEmpty f xs = Just (f xs) 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 :: (a -> a -> Ordering) -> [a] -> Maybe a
maximumByMay _ [] = Nothing maximumByMay _ [] = Nothing
......
...@@ -201,6 +201,7 @@ printDisplay disp = display disp >>= atomically . writeTChan displayChan ...@@ -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 -- | 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. -- create aren't visible. On Unix, this is usually /tmp.
switchToTmpDir :: IO ()
switchToTmpDir = void (try switchDir :: IO (Either SomeException ())) switchToTmpDir = void (try switchDir :: IO (Either SomeException ()))
where where
switchDir = switchDir =
......
...@@ -69,6 +69,7 @@ exposedName :: (a, b) -> a ...@@ -69,6 +69,7 @@ exposedName :: (a, b) -> a
exposedName = fst exposedName = fst
#endif #endif
extName (FlagSpec { flagSpecName = name }) = name
extName (FlagSpec { flagSpecName = name }) = name extName (FlagSpec { flagSpecName = name }) = name
complete :: String -> Int -> Interpreter (String, [String]) complete :: String -> Int -> Interpreter (String, [String])
......
...@@ -1110,6 +1110,7 @@ doLoadModule name modName = do ...@@ -1110,6 +1110,7 @@ doLoadModule name modName = do
return $ displayError $ "Failed to load module " ++ modName ++ ": " ++ show exception return $ displayError $ "Failed to load module " ++ modName ++ ": " ++ show exception
objTarget :: DynFlags -> HscTarget
objTarget flags = defaultObjectTarget $ targetPlatform flags objTarget flags = defaultObjectTarget $ targetPlatform flags
keepingItVariable :: Interpreter a -> Interpreter a keepingItVariable :: Interpreter a -> Interpreter a
......
...@@ -28,6 +28,7 @@ manyTillEnd p end = scan ...@@ -28,6 +28,7 @@ manyTillEnd p end = scan
xs <- scan xs <- scan
return $ x : xs return $ x : xs
manyTillEnd1 :: Parser a -> Parser [a] -> Parser [a]
manyTillEnd1 p end = do manyTillEnd1 p end = do
x <- p x <- p
xs <- manyTillEnd p end xs <- manyTillEnd p end
...@@ -39,15 +40,18 @@ unescapedChar p = try $ do ...@@ -39,15 +40,18 @@ unescapedChar p = try $ do
lookAhead p lookAhead p
return [x] return [x]
quotedString :: Parser [Char]
quotedString = do quotedString = do
quote <?> "expected starting quote" quote <?> "expected starting quote"
(manyTillEnd anyChar (unescapedChar quote) <* quote) <?> "unexpected in quoted String " (manyTillEnd anyChar (unescapedChar quote) <* quote) <?> "unexpected in quoted String "
unquotedString :: Parser [Char]
unquotedString = manyTillEnd1 anyChar end unquotedString = manyTillEnd1 anyChar end
where where
end = unescapedChar space end = unescapedChar space
<|> (lookAhead eol >> return []) <|> (lookAhead eol >> return [])
word :: Parser [Char]
word = quotedString <|> unquotedString <?> "word" word = quotedString <|> unquotedString <?> "word"
separator :: Parser String separator :: Parser String
......
...@@ -139,6 +139,7 @@ pprDynFlags show_all dflags = ...@@ -139,6 +139,7 @@ pprDynFlags show_all dflags =
flgs1 = [Opt_PrintExplicitForalls] flgs1 = [Opt_PrintExplicitForalls]
flgs2 = [Opt_PrintExplicitKinds] flgs2 = [Opt_PrintExplicitKinds]
flgs3 :: [GeneralFlag]
flgs3 = [Opt_PrintBindResult, Opt_BreakOnException, Opt_BreakOnError, Opt_PrintEvldWithShow] flgs3 = [Opt_PrintBindResult, Opt_BreakOnException, Opt_BreakOnError, Opt_PrintEvldWithShow]
-- | Pretty-print the base language and active options (taken from `InteractiveUI` module of -- | Pretty-print the base language and active options (taken from `InteractiveUI` module of
......
...@@ -132,8 +132,10 @@ installPrefixFlag :: Flag Args ...@@ -132,8 +132,10 @@ installPrefixFlag :: Flag Args
installPrefixFlag = flagReq ["prefix"] (store KernelspecInstallPrefix) "<install-dir>" installPrefixFlag = flagReq ["prefix"] (store KernelspecInstallPrefix) "<install-dir>"
"Installation prefix for kernelspec (see Jupyter's --prefix option)" "Installation prefix for kernelspec (see Jupyter's --prefix option)"
helpFlag :: Flag Args
helpFlag = flagHelpSimple (add Help) helpFlag = flagHelpSimple (add Help)
add :: Argument -> Args -> Args
add flag (Args mode flags) = Args mode $ flag : flags add flag (Args mode flags) = Args mode $ flag : flags
store :: (String -> Argument) -> String -> Args -> Either String Args store :: (String -> Argument) -> String -> Args -> Either String Args
...@@ -204,6 +206,7 @@ ihaskellArgs = ...@@ -204,6 +206,7 @@ ihaskellArgs =
where where
add flag (Args mode flags) = Args mode $ flag : flags add flag (Args mode flags) = Args mode $ flag : flags
noArgs :: Arg a
noArgs = flagArg unexpected "" noArgs = flagArg unexpected ""
where where
unexpected a = error $ "Unexpected argument: " ++ a unexpected a = error $ "Unexpected argument: " ++ a
...@@ -106,6 +106,7 @@ ipython suppress args = do ...@@ -106,6 +106,7 @@ ipython suppress args = do
else return "" else return ""
-- | Run while suppressing all output. -- | Run while suppressing all output.
quietRun :: SH.FilePath -> [Text] -> SH.Sh ()
quietRun path args = SH.runHandles path args handles nothing quietRun path args = SH.runHandles path args handles nothing
where where
handles = [SH.InHandle SH.Inherit, SH.OutHandle SH.CreatePipe, SH.ErrorHandle SH.CreatePipe] handles = [SH.InHandle SH.Inherit, SH.OutHandle SH.CreatePipe, SH.ErrorHandle SH.CreatePipe]
...@@ -267,7 +268,7 @@ getIHaskellPath = do ...@@ -267,7 +268,7 @@ getIHaskellPath = do
-- If we have an absolute path, that's the IHaskell we're interested in. -- If we have an absolute path, that's the IHaskell we're interested in.
if FP.isAbsolute f if FP.isAbsolute f
then return f then return f
else else
-- Check whether this is a relative path, or just 'IHaskell' with $PATH resolution done by -- Check whether this is a relative path, or just 'IHaskell' with $PATH resolution done by
-- the shell. If it's just 'IHaskell', use the $PATH variable to find where IHaskell lives. -- the shell. If it's just 'IHaskell', use the $PATH variable to find where IHaskell lives.
if FP.takeFileName f == f if FP.takeFileName f == f
......
...@@ -85,7 +85,7 @@ import Data.List as X hiding (head, last, tail, init, tra ...@@ -85,7 +85,7 @@ import Data.List as X hiding (head, last, tail, init, tra
elemIndices, elemIndex, findIndex, findIndices, zip5, zip6, elemIndices, elemIndex, findIndex, findIndices, zip5, zip6,
zip7, zipWith5, zipWith6, zipWith7, unzip5, unzip6, unzip6, zip7, zipWith5, zipWith6, zipWith7, unzip5, unzip6, unzip6,
delete, union, lookup, intersect, insert, deleteBy, delete, union, lookup, intersect, insert, deleteBy,
deleteFirstBy, unionBy, intersectBy, group, groupBy, insertBy, unionBy, intersectBy, group, groupBy, insertBy,
maximumBy, minimumBy, genericLength, genericDrop, genericTake, maximumBy, minimumBy, genericLength, genericDrop, genericTake,
genericSplitAt, genericIndex, genericReplicate, inits, tails) genericSplitAt, genericIndex, genericReplicate, inits, tails)
...@@ -113,13 +113,27 @@ type LByteString = Data.ByteString.Lazy.ByteString ...@@ -113,13 +113,27 @@ type LByteString = Data.ByteString.Lazy.ByteString
type LText = Data.Text.Lazy.Text type LText = Data.Text.Lazy.Text
(headMay, tailMay, lastMay, initMay, maximumMay, minimumMay) = headMay :: [a] -> Maybe a
(wrapEmpty head, wrapEmpty tail, wrapEmpty last, headMay = wrapEmpty head
wrapEmpty init, wrapEmpty maximum, wrapEmpty minimum)
where tailMay :: [a] -> Maybe [a]
wrapEmpty :: ([a] -> b) -> [a] -> Maybe b tailMay = wrapEmpty tail
wrapEmpty _ [] = Nothing
wrapEmpty f xs = Just (f xs) 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 :: (a -> a -> Ordering) -> [a] -> Maybe a
maximumByMay _ [] = Nothing maximumByMay _ [] = Nothing
......
...@@ -48,6 +48,7 @@ shouldHaveCompletionsInDirectory string expected = do ...@@ -48,6 +48,7 @@ shouldHaveCompletionsInDirectory string expected = do
unmatched = filter (not . existsInCompletion) expected unmatched = filter (not . existsInCompletion) expected
expected `shouldBeAmong` completions expected `shouldBeAmong` completions
completionHas :: String -> [String] -> IO ()
completionHas string expected = do completionHas string expected = do
(matched, completions) <- ghc $ do (matched, completions) <- ghc $ do
initCompleter initCompleter
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment