diff --git a/core/GhcMod/DynFlags.hs b/core/GhcMod/DynFlags.hs index 4bb1f24..5caa072 100644 --- a/core/GhcMod/DynFlags.hs +++ b/core/GhcMod/DynFlags.hs @@ -104,6 +104,5 @@ deferErrors df = return $ deriveEqDynFlags [d| eqDynFlags :: DynFlags -> DynFlags -> [[(Bool, String)]] - -- eqDynFlags :: DynFlags -> DynFlags -> ([Bool], [String]) eqDynFlags = undefined |] diff --git a/core/GhcMod/DynFlagsTH.hs b/core/GhcMod/DynFlagsTH.hs index 206a75e..fbcee1f 100644 --- a/core/GhcMod/DynFlagsTH.hs +++ b/core/GhcMod/DynFlagsTH.hs @@ -14,7 +14,6 @@ -- You should have received a copy of the GNU Affero General Public License -- along with this program. If not, see . -{-# OPTIONS_GHC -fno-warn-orphans #-} {-# LANGUAGE CPP, TemplateHaskell #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE DeriveDataTypeable #-} @@ -45,10 +44,6 @@ deriveEqDynFlags qds = do a <- newName "a" b <- newName "b" - -- let combFunc = [| \(bs,ss) -> (and bs, unwords ss) |] - - -- e <- AppE (VarE 'and) . ListE <$> sequence (mapMaybe (eq a b) fs) - -- e <- AppE (combFunc) . ListE <$> sequence $ combFunc (catMaybes $ map (eq a b) fs) e <- ListE <$> sequence (mapMaybe (eq a b) fs) tysig@(SigD n _) :_ <- qds @@ -103,8 +98,6 @@ deriveEqDynFlags qds = do [e| $(eqfn) $(return fa) $(return fb) |] "extraPkgConfs" -> do - -- let eqfn = [| let fn a' b' = and (zipWith eqpr (a' []) (b' [])) - -- && length (a' []) == length (b' []) let eqfn = [| let fn a' b' = cond a' b' cond a' b' = zz ++ ll @@ -159,6 +152,13 @@ deriveEqDynFlags qds = do [e| $(eqfn) $(return fa) $(return fb) |] #endif + "outputFile" -> do + let eqfn = [| let fn (Just f1) (Just f2) = [(f1 == f2, if f1 == f2 then "" else "outputFile changed")] + fn _ _ = [(True, "")] -- anything with a Nothing is fine. + in fn + |] + [e| $(eqfn) $(return fa) $(return fb) |] + "generalFlags" -> checkIntSet "generalFlags" "warningFlags" -> checkIntSet "warningFlags" diff --git a/core/GhcMod/Target.hs b/core/GhcMod/Target.hs index 6d0d318..0523fc6 100644 --- a/core/GhcMod/Target.hs +++ b/core/GhcMod/Target.hs @@ -86,9 +86,9 @@ initSession opts mdf = do df <- liftIO $ hsc_dflags <$> readIORef hsc_env_ref changed <- withLightHscEnv' (initDF crdl) $ \hsc_env -> do + gmLog GmDebug "initSession" $ text $ "outputFiles:" ++ show (outputFile $ hsc_dflags hsc_env, outputFile df) let dfEq = concat $ hsc_dflags hsc_env `eqDynFlags` df gmLog GmDebug "initSession" $ text $ "dfEq=" ++ (show $ filter (\t -> not (fst t)) dfEq) - -- gmLog GmDebug "initSession" $ text $ "dfEq=" ++ (show dfEq) let eq = and $ map fst dfEq -- return $ not $ hsc_dflags hsc_env `eqDynFlags` df return $ not eq