diff --git a/hls-graph/src/Development/IDE/Graph/Internal/Types.hs b/hls-graph/src/Development/IDE/Graph/Internal/Types.hs index 1c7d83695b..af1ff57951 100644 --- a/hls-graph/src/Development/IDE/Graph/Internal/Types.hs +++ b/hls-graph/src/Development/IDE/Graph/Internal/Types.hs @@ -110,7 +110,7 @@ keyMap = unsafePerformIO $ newIORef (GlobalKeyValueMap Map.empty IM.empty 0) {-# NOINLINE keyMap #-} -newKey :: (Eq a, Typeable a, Hashable a, Show a) => a -> Key +newKey :: (Typeable a, Hashable a, Show a) => a -> Key newKey k = unsafePerformIO $ do let !newKey = KeyValue k (T.pack (show k)) atomicModifyIORef' keyMap $ \km@(GlobalKeyValueMap hm im n) -> diff --git a/plugins/hls-alternate-number-format-plugin/src/Ide/Plugin/Conversion.hs b/plugins/hls-alternate-number-format-plugin/src/Ide/Plugin/Conversion.hs index f7795414a4..36a6fed50a 100644 --- a/plugins/hls-alternate-number-format-plugin/src/Ide/Plugin/Conversion.hs +++ b/plugins/hls-alternate-number-format-plugin/src/Ide/Plugin/Conversion.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE CPP #-} {-# LANGUAGE ViewPatterns #-} module Ide.Plugin.Conversion ( alternateFormat @@ -158,19 +159,21 @@ toBase conv header n | n < 0 = '-' : header <> upper (conv (abs n) "") | otherwise = header <> upper (conv n "") -toOctal :: (Integral a, Show a) => a -> String -toOctal = toBase showOct "0o" - -toDecimal :: Integral a => a -> String -toDecimal = toBase showInt "" +#if MIN_VERSION_base(4,17,0) +toOctal, toDecimal, toBinary, toHex :: Integral a => a -> String +#else +toOctal, toDecimal, toBinary, toHex:: (Integral a, Show a) => a -> String +#endif -toBinary :: (Integral a, Show a) => a -> String toBinary = toBase showBin_ "0b" where - -- this is not defined in versions of Base < 4.16-ish + -- this is not defined in base < 4.16 showBin_ = showIntAtBase 2 intToDigit -toHex :: (Integral a, Show a) => a -> String +toOctal = toBase showOct "0o" + +toDecimal = toBase showInt "" + toHex = toBase showHex "0x" toFloatDecimal :: RealFloat a => a -> String diff --git a/plugins/hls-alternate-number-format-plugin/src/Ide/Plugin/Literals.hs b/plugins/hls-alternate-number-format-plugin/src/Ide/Plugin/Literals.hs index 9179bd824c..233745f021 100644 --- a/plugins/hls-alternate-number-format-plugin/src/Ide/Plugin/Literals.hs +++ b/plugins/hls-alternate-number-format-plugin/src/Ide/Plugin/Literals.hs @@ -15,8 +15,7 @@ import qualified Data.Text.Encoding as T #endif import Development.IDE.GHC.Compat hiding (getSrcSpan) import Development.IDE.Graph.Classes (NFData (rnf)) -import Generics.SYB (Data, Typeable, everything, - extQ) +import Generics.SYB (Data, everything, extQ) import qualified GHC.Generics as GHC -- data type to capture what type of literal we are dealing with @@ -49,7 +48,7 @@ getSrcSpan = \case FracLiteral ss _ _ -> unLit ss -- | Find all literals in a Parsed Source File -collectLiterals :: (Data ast, Typeable ast) => ast -> [Literal] +collectLiterals :: Data ast => ast -> [Literal] collectLiterals = everything (<>) (maybeToList . (const Nothing `extQ` getLiteral `extQ` getPattern)) diff --git a/plugins/hls-alternate-number-format-plugin/test/Properties/Conversion.hs b/plugins/hls-alternate-number-format-plugin/test/Properties/Conversion.hs index bce519112d..07e4617bde 100644 --- a/plugins/hls-alternate-number-format-plugin/test/Properties/Conversion.hs +++ b/plugins/hls-alternate-number-format-plugin/test/Properties/Conversion.hs @@ -15,7 +15,7 @@ conversions = testGroup "Conversions" $ ] <> map (uncurry testProperty) - [ ("Match HexFloat", prop_regexMatchesHexFloat @Double) + [ ("Match HexFloat", prop_regexMatchesHexFloat) , ("Match FloatDecimal", prop_regexMatchesFloatDecimal) , ("Match FloatExpDecimal", prop_regexMatchesFloatExpDecimal) ] @@ -23,20 +23,20 @@ conversions = testGroup "Conversions" $ prop_regexMatchesNumDecimal :: Integer -> Bool prop_regexMatchesNumDecimal = (=~ numDecimalRegex) . toFloatExpDecimal @Double . fromInteger -prop_regexMatchesHex :: (Integral a, Show a) => a -> Bool +prop_regexMatchesHex :: Integer -> Bool prop_regexMatchesHex = (=~ hexRegex ) . toHex -prop_regexMatchesOctal :: (Integral a, Show a) => a -> Bool +prop_regexMatchesOctal :: Integer -> Bool prop_regexMatchesOctal = (=~ octalRegex) . toOctal -prop_regexMatchesBinary :: (Integral a, Show a) => a -> Bool +prop_regexMatchesBinary :: Integer -> Bool prop_regexMatchesBinary = (=~ binaryRegex) . toBinary -prop_regexMatchesHexFloat :: (RealFloat a) => a -> Bool +prop_regexMatchesHexFloat :: Double -> Bool prop_regexMatchesHexFloat = (=~ hexFloatRegex) . toHexFloat -prop_regexMatchesFloatDecimal :: (RealFloat a) => a -> Bool +prop_regexMatchesFloatDecimal :: Double -> Bool prop_regexMatchesFloatDecimal = (=~ decimalRegex ) . toFloatDecimal -prop_regexMatchesFloatExpDecimal :: (RealFloat a) => a -> Bool +prop_regexMatchesFloatExpDecimal :: Double -> Bool prop_regexMatchesFloatExpDecimal = (=~ numDecimalRegex ) . toFloatExpDecimal diff --git a/plugins/hls-call-hierarchy-plugin/src/Ide/Plugin/CallHierarchy/Internal.hs b/plugins/hls-call-hierarchy-plugin/src/Ide/Plugin/CallHierarchy/Internal.hs index 8ab338f7eb..8eac1bbd8f 100644 --- a/plugins/hls-call-hierarchy-plugin/src/Ide/Plugin/CallHierarchy/Internal.hs +++ b/plugins/hls-call-hierarchy-plugin/src/Ide/Plugin/CallHierarchy/Internal.hs @@ -243,8 +243,8 @@ mkCallHierarchyCall mk v@Vertex{..} = do [] -> pure Nothing -- | Unified queries include incoming calls and outgoing calls. -queryCalls :: (Show a) - => CallHierarchyItem +queryCalls :: + CallHierarchyItem -> (HieDb -> Symbol -> IO [Vertex]) -> (Vertex -> Action (Maybe a)) -> ([a] -> [a]) diff --git a/plugins/hls-change-type-signature-plugin/src/Ide/Plugin/ChangeTypeSignature.hs b/plugins/hls-change-type-signature-plugin/src/Ide/Plugin/ChangeTypeSignature.hs index 88e7865a4b..df776e6d15 100644 --- a/plugins/hls-change-type-signature-plugin/src/Ide/Plugin/ChangeTypeSignature.hs +++ b/plugins/hls-change-type-signature-plugin/src/Ide/Plugin/ChangeTypeSignature.hs @@ -70,15 +70,12 @@ data ChangeSignature = ChangeSignature { , diagnostic :: Diagnostic } --- | Constraint needed to trackdown OccNames in signatures -type SigName = (HasOccName (IdP GhcPs)) - -- | Create a CodeAction from a Diagnostic -generateAction :: SigName => PluginId -> Uri -> [LHsDecl GhcPs] -> Diagnostic -> Maybe (Command |? CodeAction) +generateAction :: PluginId -> Uri -> [LHsDecl GhcPs] -> Diagnostic -> Maybe (Command |? CodeAction) generateAction plId uri decls diag = changeSigToCodeAction plId uri <$> diagnosticToChangeSig decls diag -- | Convert a diagnostic into a ChangeSignature and add the proper SrcSpan -diagnosticToChangeSig :: SigName => [LHsDecl GhcPs] -> Diagnostic -> Maybe ChangeSignature +diagnosticToChangeSig :: [LHsDecl GhcPs] -> Diagnostic -> Maybe ChangeSignature diagnosticToChangeSig decls diagnostic = do -- regex match on the GHC Error Message (expectedType, actualType, declName) <- matchingDiagnostic diagnostic @@ -107,7 +104,7 @@ errorMessageRegexes = [ -- be sure to add new Error Messages Regexes at the bott -- | Given a String with the name of a declaration, GHC's "Expected Type", find the declaration that matches -- both the name given and the Expected Type, and return the type signature location -findSigLocOfStringDecl :: SigName => [LHsDecl GhcPs] -> ExpectedSig -> String -> Maybe RealSrcSpan +findSigLocOfStringDecl :: [LHsDecl GhcPs] -> ExpectedSig -> String -> Maybe RealSrcSpan findSigLocOfStringDecl decls expectedType declName = something (const Nothing `extQ` findSig `extQ` findLocalSig) decls where -- search for Top Level Signatures diff --git a/plugins/hls-eval-plugin/src/Ide/Plugin/Eval/Parse/Comments.hs b/plugins/hls-eval-plugin/src/Ide/Plugin/Eval/Parse/Comments.hs index 4f99abaa5d..d1ef5e06c8 100644 --- a/plugins/hls-eval-plugin/src/Ide/Plugin/Eval/Parse/Comments.hs +++ b/plugins/hls-eval-plugin/src/Ide/Plugin/Eval/Parse/Comments.hs @@ -301,7 +301,7 @@ blockProp = do AProp ran prop <$> resultBlockP withRange :: - (TraversableStream s, Stream s, Monad m, Ord v, Traversable t) => + (TraversableStream s, Ord v, Traversable t) => ParsecT v s m (t (a, Position)) -> ParsecT v s m (Range, t a) withRange p = do @@ -489,7 +489,7 @@ consume style = Line -> (,) <$> takeRest <*> getPosition Block {} -> manyTill_ anySingle (getPosition <* eob) -getPosition :: (Monad m, Ord v, TraversableStream s) => ParsecT v s m Position +getPosition :: (Ord v, TraversableStream s) => ParsecT v s m Position getPosition = sourcePosToPosition <$> getSourcePos -- | Parses example test line. diff --git a/plugins/hls-overloaded-record-dot-plugin/src/Ide/Plugin/OverloadedRecordDot.hs b/plugins/hls-overloaded-record-dot-plugin/src/Ide/Plugin/OverloadedRecordDot.hs index 4d8a4aa3ef..03b62b4a5b 100644 --- a/plugins/hls-overloaded-record-dot-plugin/src/Ide/Plugin/OverloadedRecordDot.hs +++ b/plugins/hls-overloaded-record-dot-plugin/src/Ide/Plugin/OverloadedRecordDot.hs @@ -50,10 +50,9 @@ import Development.IDE.GHC.Compat (Extension (OverloadedReco GhcPass, HsExpansion (HsExpanded), HsExpr (HsApp, HsVar, OpApp, XExpr), - LHsExpr, Outputable, - Pass (..), appPrec, - dollarName, getLoc, - hs_valds, + LHsExpr, Pass (..), + appPrec, dollarName, + getLoc, hs_valds, parenthesizeHsExpr, pattern RealSrcSpan, unLoc) @@ -264,9 +263,7 @@ convertRecordSelectors RecordSelectorExpr{..} = -- |Converts a record selector expression into record dot syntax, currently we -- are using printOutputable to do it. We are also letting GHC decide when to -- parenthesize the record expression -convertRecSel :: Outputable (LHsExpr (GhcPass 'Renamed)) - => LHsExpr (GhcPass 'Renamed) - -> LHsExpr (GhcPass 'Renamed) -> Text +convertRecSel :: LHsExpr (GhcPass 'Renamed) -> LHsExpr (GhcPass 'Renamed) -> Text convertRecSel se re = printOutputable (parenthesizeHsExpr appPrec re) <> "." <> printOutputable se diff --git a/plugins/hls-refactor-plugin/src/Development/IDE/GHC/Dump.hs b/plugins/hls-refactor-plugin/src/Development/IDE/GHC/Dump.hs index b19b972feb..affd44e1bc 100644 --- a/plugins/hls-refactor-plugin/src/Development/IDE/GHC/Dump.hs +++ b/plugins/hls-refactor-plugin/src/Development/IDE/GHC/Dump.hs @@ -13,7 +13,7 @@ import GHC.Plugins hiding (AnnLet) import Prelude hiding ((<>)) -- | Show a GHC syntax tree in HTML. -showAstDataHtml :: (Data a, ExactPrint a, Outputable a) => a -> SDoc +showAstDataHtml :: (Data a, ExactPrint a) => a -> SDoc showAstDataHtml a0 = html $ header $$ body (tag' [("id",text (show @String "myUL"))] "ul" $ vcat @@ -244,8 +244,7 @@ showAstDataHtml a0 = html $ annotationEpaLocation :: EpAnn EpaLocation -> SDoc annotationEpaLocation = annotation' (text "EpAnn EpaLocation") - annotation' :: forall a .(Data a, Typeable a) - => SDoc -> EpAnn a -> SDoc + annotation' :: forall a. Data a => SDoc -> EpAnn a -> SDoc annotation' tag anns = nested (text $ showConstr (toConstr anns)) (vcat (map li $ gmapQ showAstDataHtml' anns)) @@ -266,16 +265,16 @@ showAstDataHtml a0 = html $ srcSpanAnnN :: SrcSpanAnn' (EpAnn NameAnn) -> SDoc srcSpanAnnN = locatedAnn'' (text "SrcSpanAnnN") - locatedAnn'' :: forall a. (Typeable a, Data a) + locatedAnn'' :: forall a. Data a => SDoc -> SrcSpanAnn' a -> SDoc locatedAnn'' tag ss = case cast ss of Just ((SrcSpanAnn ann s) :: SrcSpanAnn' a) -> - nested "SrcSpanAnn" $ ( + nested "SrcSpanAnn" ( li(showAstDataHtml' ann) $$ li(srcSpan s)) Nothing -> text "locatedAnn:unmatched" <+> tag - <+> (text (showConstr (toConstr ss))) + <+> text (showConstr (toConstr ss)) normalize_newlines :: String -> String diff --git a/plugins/hls-refactor-plugin/src/Development/IDE/GHC/ExactPrint.hs b/plugins/hls-refactor-plugin/src/Development/IDE/GHC/ExactPrint.hs index f8ca0aa13f..f249711e4c 100644 --- a/plugins/hls-refactor-plugin/src/Development/IDE/GHC/ExactPrint.hs +++ b/plugins/hls-refactor-plugin/src/Development/IDE/GHC/ExactPrint.hs @@ -258,7 +258,7 @@ needsParensSpace _ = mempty -} graft' :: forall ast a l. - (Data a, Typeable l, ASTElement l ast) => + (Data a, ASTElement l ast) => -- | Do we need to insert a space before this grafting? In do blocks, the -- answer is no, or we will break layout. But in function applications, -- the answer is yes, or the function call won't get its argument. Yikes! @@ -348,7 +348,7 @@ graftExprWithM dst trans = Graft $ \dflags a -> do graftWithM :: forall ast m a l. - (Fail.MonadFail m, Data a, Typeable l, ASTElement l ast) => + (Fail.MonadFail m, Data a, ASTElement l ast) => SrcSpan -> (LocatedAn l ast -> TransformT m (Maybe (LocatedAn l ast))) -> Graft m a @@ -643,7 +643,7 @@ instance ASTElement NameAnn RdrName where -- | Given an 'LHSExpr', compute its exactprint annotations. -- Note that this function will throw away any existing annotations (and format) -annotate :: (ASTElement l ast, Outputable l) +annotate :: ASTElement l ast => DynFlags -> Bool -> LocatedAn l ast -> TransformT (Either String) (LocatedAn l ast) annotate dflags needs_space ast = do uniq <- show <$> uniqueSrcSpanT diff --git a/plugins/hls-refactor-plugin/src/Development/IDE/Plugin/CodeAction/Util.hs b/plugins/hls-refactor-plugin/src/Development/IDE/Plugin/CodeAction/Util.hs index 197c936165..40f3c76127 100644 --- a/plugins/hls-refactor-plugin/src/Development/IDE/Plugin/CodeAction/Util.hs +++ b/plugins/hls-refactor-plugin/src/Development/IDE/Plugin/CodeAction/Util.hs @@ -27,7 +27,7 @@ debugAST :: Bool debugAST = unsafePerformIO (getEnvDefault "GHCIDE_DEBUG_AST" "0") == "1" -- | Prints an 'Outputable' value to stderr and to an HTML file for further inspection -traceAst :: (Data a, ExactPrint a, Outputable a, HasCallStack) => String -> a -> a +traceAst :: (Data a, ExactPrint a, HasCallStack) => String -> a -> a traceAst lbl x | debugAST = trace doTrace x | otherwise = x diff --git a/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs b/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs index 2220306c13..06efa793c2 100644 --- a/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs +++ b/plugins/hls-rename-plugin/src/Ide/Plugin/Rename.hs @@ -148,7 +148,7 @@ replaceRefs newName refs = everywhere $ -- replaceLoc @NoEpAnns `extT` -- not needed replaceLoc @NameAnn where - replaceLoc :: forall an. Typeable an => LocatedAn an RdrName -> LocatedAn an RdrName + replaceLoc :: forall an. LocatedAn an RdrName -> LocatedAn an RdrName replaceLoc (L srcSpan oldRdrName) | isRef (locA srcSpan) = L srcSpan $ replace oldRdrName replaceLoc lOldRdrName = lOldRdrName @@ -217,7 +217,7 @@ removeGenerated HAR{..} = HAR{hieAst = go hieAst,..} goAst (Node nsi sp xs) = Node (SourcedNodeInfo $ M.restrictKeys (getSourcedNodeInfo nsi) (S.singleton SourceInfo)) sp (map goAst xs) -- head is safe since groups are non-empty -collectWith :: (Hashable a, Eq a, Eq b) => (a -> b) -> HashSet a -> [(b, HashSet a)] +collectWith :: (Hashable a, Eq b) => (a -> b) -> HashSet a -> [(b, HashSet a)] collectWith f = map (\a -> (f $ head a, HS.fromList a)) . groupOn f . HS.toList locToUri :: Location -> Uri diff --git a/plugins/hls-retrie-plugin/src/Ide/Plugin/Retrie.hs b/plugins/hls-retrie-plugin/src/Ide/Plugin/Retrie.hs index 4125ded8e0..46e9750683 100644 --- a/plugins/hls-retrie-plugin/src/Ide/Plugin/Retrie.hs +++ b/plugins/hls-retrie-plugin/src/Ide/Plugin/Retrie.hs @@ -54,10 +54,9 @@ import Development.IDE.GHC.Compat (GRHSs (GRHSs), HsExpr (HsApp, OpApp), HsGroup (..), HsValBindsLR (..), - HscEnv, IdP, - ImportDecl (..), LHsExpr, - LRuleDecls, Match, - ModIface, + HscEnv, ImportDecl (..), + LHsExpr, LRuleDecls, + Match, ModIface, ModSummary (ModSummary, ms_hspp_buf, ms_mod), Outputable, ParsedModule, RuleDecl (HsRule), @@ -425,7 +424,6 @@ describeRestriction restrictToOriginatingFile = if restrictToOriginatingFile then " in current file" else "" suggestTypeRewrites :: - (Outputable (IdP GhcRn)) => Uri -> GHC.Module -> TyClDecl GhcRn ->