Skip to content
Snippets Groups Projects
Commit fc462513 authored by Mateusz Kowalczyk's avatar Mateusz Kowalczyk
Browse files

Fix warnings

parent 267e2c2e
No related branches found
No related tags found
No related merge requests found
...@@ -235,7 +235,6 @@ synifyTyCon coax tc ...@@ -235,7 +235,6 @@ synifyTyCon coax tc
use_gadt_syntax = any (not . isVanillaDataCon) (tyConDataCons tc) use_gadt_syntax = any (not . isVanillaDataCon) (tyConDataCons tc)
consRaw = map (synifyDataCon use_gadt_syntax) (tyConDataCons tc) consRaw = map (synifyDataCon use_gadt_syntax) (tyConDataCons tc)
cons = rights consRaw cons = rights consRaw
dataConErrs = lefts consRaw
-- "deriving" doesn't affect the signature, no need to specify any. -- "deriving" doesn't affect the signature, no need to specify any.
alg_deriv = Nothing alg_deriv = Nothing
defn = HsDataDefn { dd_ND = alg_nd defn = HsDataDefn { dd_ND = alg_nd
...@@ -248,7 +247,7 @@ synifyTyCon coax tc ...@@ -248,7 +247,7 @@ synifyTyCon coax tc
[] -> return $ [] -> return $
DataDecl { tcdLName = name, tcdTyVars = tyvars, tcdDataDefn = defn DataDecl { tcdLName = name, tcdTyVars = tyvars, tcdDataDefn = defn
, tcdFVs = placeHolderNames } , tcdFVs = placeHolderNames }
ms -> Left $ unlines dataConErrs dataConErrs -> Left $ unlines dataConErrs
-- User beware: it is your responsibility to pass True (use_gadt_syntax) -- User beware: it is your responsibility to pass True (use_gadt_syntax)
-- for any constructor that would be misrepresented by omitting its -- for any constructor that would be misrepresented by omitting its
......
...@@ -25,14 +25,13 @@ import Data.Function (on) ...@@ -25,14 +25,13 @@ import Data.Function (on)
import qualified Data.Map as Map import qualified Data.Map as Map
import qualified Data.Set as Set import qualified Data.Set as Set
import Bag (listToBag)
import Class import Class
import DynFlags import DynFlags
import ErrUtils import ErrUtils
import FamInstEnv import FamInstEnv
import FastString import FastString
import GHC import GHC
import GhcMonad (withSession, logWarnings) import GhcMonad (withSession)
import Id import Id
import InstEnv import InstEnv
import MonadUtils (liftIO) import MonadUtils (liftIO)
......
...@@ -620,8 +620,8 @@ hiDecl dflags t = do ...@@ -620,8 +620,8 @@ hiDecl dflags t = do
return Nothing return Nothing
Just x -> case tyThingToLHsDecl x of Just x -> case tyThingToLHsDecl x of
Left m -> liftErrMsg (tell [bugWarn m]) >> return Nothing Left m -> liftErrMsg (tell [bugWarn m]) >> return Nothing
Right (m, t) -> liftErrMsg (tell $ map bugWarn m) Right (m, t') -> liftErrMsg (tell $ map bugWarn m)
>> return (Just $ noLoc t) >> return (Just $ noLoc t')
where where
warnLine x = O.text "haddock-bug:" O.<+> O.text x O.<> warnLine x = O.text "haddock-bug:" O.<+> O.text x O.<>
O.comma O.<+> O.quotes (O.ppr t) O.<+> O.comma O.<+> O.quotes (O.ppr t) O.<+>
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment