View patterns, record wildcards, and record puns
[ghc-hetmet.git] / compiler / main / HeaderInfo.hs
index e124e37..a680695 100644 (file)
@@ -1,3 +1,10 @@
+{-# OPTIONS -w #-}
+-- The above warning supression flag is a temporary kludge.
+-- While working on this module you are encouraged to remove it and fix
+-- any warnings in the module. See
+--     http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#Warnings
+-- for details
+
 -----------------------------------------------------------------------------
 --
 -- Parsing the top of a Haskell source file to get its module name,
@@ -8,7 +15,7 @@
 --
 -----------------------------------------------------------------------------
 
-module HeaderInfo ( getImportsFromFile, getImports
+module HeaderInfo ( getImports
                   , getOptionsFromFile, getOptions
                   , optionsErrorMsgs ) where
 
@@ -22,8 +29,8 @@ import Module         ( ModuleName, moduleName )
 import PrelNames        ( gHC_PRIM, mAIN_NAME )
 import StringBuffer    ( StringBuffer(..), hGetStringBuffer, hGetStringBufferBlock
                         , appendStringBuffers )
+import Config
 import SrcLoc
-import FastString      ( mkFastString )
 import DynFlags
 import ErrUtils
 import Util
@@ -33,8 +40,6 @@ import Panic
 import Maybes
 import Bag             ( emptyBag, listToBag )
 
-import Distribution.Compiler
-
 import Control.Exception
 import Control.Monad
 import System.Exit
@@ -51,18 +56,9 @@ import IOExts                   ( openFileEx, IOModeEx(..) )
 openBinaryFile fp mode = openFileEx fp (BinaryMode mode)
 #endif
 
--- getImportsFromFile is careful to close the file afterwards, otherwise
--- we can end up with a large number of open handles before the garbage
--- collector gets around to closing them.
-getImportsFromFile :: DynFlags -> FilePath
-   -> IO ([Located ModuleName], [Located ModuleName], Located ModuleName)
-getImportsFromFile dflags filename = do
-  buf <- hGetStringBuffer filename
-  getImports dflags buf filename
-
-getImports :: DynFlags -> StringBuffer -> FilePath
+getImports :: DynFlags -> StringBuffer -> FilePath -> FilePath
     -> IO ([Located ModuleName], [Located ModuleName], Located ModuleName)
-getImports dflags buf filename = do
+getImports dflags buf filename source_filename = do
   let loc  = mkSrcLoc (mkFastString filename) 1 0
   case unP parseHeader (mkPState buf loc dflags) of
        PFailed span err -> parseError span err
@@ -73,7 +69,8 @@ getImports dflags buf filename = do
          case rdr_module of
            L _ (HsModule mb_mod _ imps _ _ _ _ _) ->
              let
-               mod = mb_mod `orElse` L (srcLocSpan loc) mAIN_NAME
+                main_loc = mkSrcLoc (mkFastString source_filename) 1 0
+               mod = mb_mod `orElse` L (srcLocSpan main_loc) mAIN_NAME
                (src_idecls, ord_idecls) = partition isSourceIdecl (map unLoc imps)
                source_imps   = map getImpMod src_idecls        
                ordinary_imps = filter ((/= moduleName gHC_PRIM) . unLoc) 
@@ -177,11 +174,13 @@ getOptions' buf filename
 
 checkExtension :: Located FastString -> Located String
 checkExtension (L l ext)
-    = case reads (unpackFS ext) of
-        [] -> languagePragParseError l
-        (okExt,""):_ -> case extensionsToGHCFlag [okExt] of
-                          ([],[opt]) -> L l opt
-                          _ -> unsupportedExtnError l okExt
+-- Checks if a given extension is valid, and if so returns
+-- its corresponding flag. Otherwise it throws an exception.
+ =  let ext' = unpackFS ext in
+    if ext' `elem` supportedLanguages
+       || ext' `elem` (map ("No"++) supportedLanguages)
+    then L l ("-X"++ext')
+    else unsupportedExtnError l ext'
 
 languagePragParseError loc =
   pgmError (showSDoc (mkLocMessage loc (
@@ -190,7 +189,7 @@ languagePragParseError loc =
 unsupportedExtnError loc unsup =
   pgmError (showSDoc (mkLocMessage loc (
                 text "unsupported extension: " <>
-                (text.show) unsup)))
+                text unsup)))
 
 
 optionsErrorMsgs :: [String] -> [Located String] -> FilePath -> Messages