diff --git a/compiler/main/HscMain.hs b/compiler/main/HscMain.hs
index 15a175fbcfa6504c76166e2f813051956968f3b8..f8e2b5df26530646645344b8071c380c8848fb79 100644
--- a/compiler/main/HscMain.hs
+++ b/compiler/main/HscMain.hs
@@ -1011,8 +1011,8 @@ hscCheckSafe' dflags m l = do
         case iface of
             -- can't load iface to check trust!
             Nothing -> throwErrors $ unitBag $ mkPlainErrMsg l
-                        $ text "Can't load the interface file for" <+> ppr m <>
-                          text ", to check that it can be safely imported"
+                         $ text "Can't load the interface file for" <+> ppr m
+                           <> text ", to check that it can be safely imported"
 
             -- got iface, check trust
             Just iface' -> do
@@ -1026,18 +1026,19 @@ hscCheckSafe' dflags m l = do
                     -- General errors we throw but Safe errors we log
                     (True, True ) -> return $ trust == Sf_Trustworthy
                     (True, False) -> liftIO . throwIO $ pkgTrustErr
-                    (False, _   ) -> logWarnings modTrustErr >> return (trust == Sf_Trustworthy)
+                    (False, _   ) -> logWarnings modTrustErr
+                                     >> return (trust == Sf_Trustworthy)
 
                 where
                     pkgTrustErr = mkSrcErr $ unitBag $ mkPlainErrMsg l $
-                        sep [ ppr (moduleName m) <> text ":"
-                            , text "Can't be safely imported!"
+                        sep [ ppr (moduleName m)
+                                <> text ": Can't be safely imported!"
                             , text "The package (" <> ppr (modulePackageId m)
-                                  <> text ") the module resides in isn't trusted."
+                                <> text ") the module resides in isn't trusted."
                             ]
                     modTrustErr = unitBag $ mkPlainErrMsg l $
-                        sep [ ppr (moduleName m) <> text ":"
-                            , text "Can't be safely imported!"
+                        sep [ ppr (moduleName m)
+                                <> text ": Can't be safely imported!"
                             , text "The module itself isn't safe." ]
 
     -- | Check the package a module resides in is trusted. Safe compiled
@@ -1081,8 +1082,8 @@ checkPkgTrust dflags pkgs =
             = Nothing
             | otherwise
             = Just $ mkPlainErrMsg noSrcSpan
-                   $ text "The package (" <> ppr pkg <> text ") is required"
-                  <> text " to be trusted but it isn't!"
+                   $ text "The package (" <> ppr pkg <> text ") is required" <>
+                     text " to be trusted but it isn't!"
 
 -- | Set module to unsafe and wipe trust information.
 --
@@ -1106,19 +1107,15 @@ wipeTrust tcg_env whyUnsafe = do
     whyUnsafe' df = vcat [ text "Warning:" <+> quotes pprMod
                              <+> text "has been infered as unsafe!"
                        , text "Reason:"
-                       , nest 4 $
-                           (vcat $ badFlags df) $+$
-                           (vcat $ pprErrMsgBagWithLoc whyUnsafe)
+                       , nest 4 $ (vcat $ badFlags df) $+$
+                                  (vcat $ pprErrMsgBagWithLoc whyUnsafe)
                        ]
-
     badFlags df   = concat $ map (badFlag df) unsafeFlags
-
     badFlag df (str,loc,on,_)
         | on df     = [mkLocMessage (loc df) $
                             text str <+> text "is not allowed in Safe Haskell"]
         | otherwise = []
 
-
 --------------------------------------------------------------
 -- Simplifiers
 --------------------------------------------------------------