Hi,

The document of GHC API says that "desugarModule" displays warnings of
pattern matching even if HscNothing is specified:

        
http://www.haskell.org/ghc/docs/latest/html/libraries/ghc/GHC.html#t:HscTarget

Unfortunately, I cannot get warnings of pattern matching. To
demonstrate this, I attached two files:

- Main.hs -- using "desugarModule"
- B.hs    -- a target file: top level signature is missing,
             pattern is imcompleted

When I run "Main.hs" with:
        % runghc -- -package --ghc-arg=ghc -Wall Main
I only got:
        B.hs:6:1: Warning:
            Top-level binding with no type signature: main :: IO ()

Does anyone know how to display warnings of pattern matching with
HscNothing?

--Kazu

<Main>
-- runghc -- -package --ghc-arg=ghc A

module Main where

import GHC
import GHC.Paths (libdir)
import DynFlags

main :: IO ()
main = defaultErrorHandler defaultFatalMessager defaultFlushOut $ runGhc (Just 
libdir) $ getWarings "B.hs" "B"

getWarings :: String -> String -> Ghc ()
getWarings targetFile targetModule = do
    dflags <- getSessionDynFlags
    let dflags' = dflags {
            ghcLink   = NoLink
          , hscTarget = HscNothing
          }
        dflags'' = foldl wopt_set dflags' 
[Opt_WarnMissingSigs,Opt_WarnIncompletePatterns]
    _ <- setSessionDynFlags dflags''
    target <- guessTarget targetFile Nothing
    setTargets [target]
    _ <- load LoadAllTargets
    modSum <- getModSummary $ mkModuleName targetModule
    p <- parseModule modSum
    t <- typecheckModule p
    _ <- desugarModule t
    return ()
</Main>
<B>
module B where

myHead ::  [Int] -> Int
myHead (x:_) = x

main = do
    print $ myHead [1,2,3]
</B>

_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to