Columns now start at 1, as lines already did
authorIan Lynagh <igloo@earth.li>
Fri, 27 Nov 2009 22:40:50 +0000 (22:40 +0000)
committerIan Lynagh <igloo@earth.li>
Fri, 27 Nov 2009 22:40:50 +0000 (22:40 +0000)
Also corrected a couple of line 0's to line 1

compiler/basicTypes/SrcLoc.lhs
compiler/cmm/CmmLex.x
compiler/cmm/CmmParse.y
compiler/iface/MkIface.lhs
compiler/main/GHC.hs
compiler/main/HeaderInfo.hs
compiler/main/HscMain.lhs
compiler/parser/Lexer.x
compiler/parser/Parser.y.pp

index 02c3e8a..35c78a8 100644 (file)
@@ -87,10 +87,7 @@ this is the obvious stuff:
 data SrcLoc
   = SrcLoc     FastString      -- A precise location (file name)
                {-# UNPACK #-} !Int             -- line number, begins at 1
-               {-# UNPACK #-} !Int             -- column number, begins at 0
-               -- Don't ask me why lines start at 1 and columns start at
-               -- zero.  That's just the way it is, so there.  --SDM
-
+               {-# UNPACK #-} !Int             -- column number, begins at 1
   | UnhelpfulLoc FastString    -- Just a general indication
 \end{code}
 
@@ -137,7 +134,7 @@ srcLocCol _other         = panic "srcLocCol: unknown col"
 -- | Move the 'SrcLoc' down by one line if the character is a newline
 -- and across by one character in any other case
 advanceSrcLoc :: SrcLoc -> Char -> SrcLoc
-advanceSrcLoc (SrcLoc f l _) '\n' = SrcLoc f  (l + 1) 0
+advanceSrcLoc (SrcLoc f l _) '\n' = SrcLoc f  (l + 1) 1
 advanceSrcLoc (SrcLoc f l c) _    = SrcLoc f  l (c + 1)
 advanceSrcLoc loc           _    = loc -- Better than nothing
 \end{code}
index d4aca18..bfc18c1 100644 (file)
@@ -269,7 +269,7 @@ tok_string str = CmmT_String (read str)
 setLine :: Int -> Action
 setLine code span buf len = do
   let line = parseUnsignedInteger buf len 10 octDecDigit
-  setSrcLoc (mkSrcLoc (srcSpanFile span) (fromIntegral line - 1) 0)
+  setSrcLoc (mkSrcLoc (srcSpanFile span) (fromIntegral line - 1) 1)
        -- subtract one: the line number refers to the *following* line
   -- trace ("setLine "  ++ show line) $ do
   popLexState
index c3a37b2..ff6358d 100644 (file)
@@ -1025,7 +1025,7 @@ parseCmmFile dflags filename = do
   showPass dflags "ParseCmm"
   buf <- hGetStringBuffer filename
   let
-       init_loc = mkSrcLoc (mkFastString filename) 1 0
+       init_loc = mkSrcLoc (mkFastString filename) 1 1
        init_state = (mkPState buf init_loc dflags) { lex_state = [0] }
                -- reset the lex_state: the Lexer monad leaves some stuff
                -- in there we don't want.
index f271aa5..cad384c 100644 (file)
@@ -741,7 +741,7 @@ ruleOrphWarn unqual mod rule
   = mkWarnMsg silly_loc unqual $
     ptext (sLit "Orphan rule:") <+> ppr rule
   where
-    silly_loc = srcLocSpan (mkSrcLoc (moduleNameFS (moduleName mod)) 1 0)
+    silly_loc = srcLocSpan (mkSrcLoc (moduleNameFS (moduleName mod)) 1 1)
     -- We don't have a decent SrcSpan for a Rule, not even the CoreRule
     -- Could readily be fixed by adding a SrcSpan to CoreRule, if we wanted to
 
index 0be0fc4..5289f71 100644 (file)
@@ -2580,7 +2580,7 @@ getModuleSourceAndFlags mod = do
 getTokenStream :: GhcMonad m => Module -> m [Located Token]
 getTokenStream mod = do
   (sourceFile, source, flags) <- getModuleSourceAndFlags mod
-  let startLoc = mkSrcLoc (mkFastString sourceFile) 0 0
+  let startLoc = mkSrcLoc (mkFastString sourceFile) 1 1
   case lexTokenStream source startLoc flags of
     POk _ ts  -> return ts
     PFailed span err -> throw $ mkSrcErr (unitBag $ mkPlainErrMsg span err)
@@ -2591,7 +2591,7 @@ getTokenStream mod = do
 getRichTokenStream :: GhcMonad m => Module -> m [(Located Token, String)]
 getRichTokenStream mod = do
   (sourceFile, source, flags) <- getModuleSourceAndFlags mod
-  let startLoc = mkSrcLoc (mkFastString sourceFile) 0 0
+  let startLoc = mkSrcLoc (mkFastString sourceFile) 1 1
   case lexTokenStream source startLoc flags of
     POk _ ts -> return $ addSourceToTokens startLoc source ts
     PFailed span err -> throw $ mkSrcErr (unitBag $ mkPlainErrMsg span err)
@@ -2622,7 +2622,7 @@ addSourceToTokens loc buf (t@(L span _) : ts)
 showRichTokenStream :: [(Located Token, String)] -> String
 showRichTokenStream ts = go startLoc ts ""
     where sourceFile = srcSpanFile (getLoc . fst . head $ ts)
-          startLoc = mkSrcLoc sourceFile 0 0
+          startLoc = mkSrcLoc sourceFile 1 1
           go _ [] = id
           go loc ((L span _, str):ts)
               | not (isGoodSrcSpan span) = go loc ts
index c3c78ae..597253e 100644 (file)
@@ -55,7 +55,7 @@ getImports :: GhcMonad m =>
            -> m ([Located (ImportDecl RdrName)], [Located (ImportDecl RdrName)], Located ModuleName)
               -- ^ The source imports, normal imports, and the module name.
 getImports dflags buf filename source_filename = do
-  let loc  = mkSrcLoc (mkFastString filename) 1 0
+  let loc  = mkSrcLoc (mkFastString filename) 1 1
   case unP parseHeader (mkPState buf loc dflags) of
     PFailed span err -> parseError span err
     POk pst rdr_module -> do
@@ -70,7 +70,7 @@ getImports dflags buf filename source_filename = do
          case rdr_module of
            L _ (HsModule mb_mod _ imps _ _ _) ->
              let
-                main_loc = mkSrcLoc (mkFastString source_filename) 1 0
+                main_loc = mkSrcLoc (mkFastString source_filename) 1 1
                mod = mb_mod `orElse` L (srcLocSpan main_loc) mAIN_NAME
                (src_idecls, ord_idecls) = partition (ideclSource.unLoc) imps
                ordinary_imps = filter ((/= moduleName gHC_PRIM) . unLoc . ideclName . unLoc) 
@@ -109,7 +109,7 @@ lazyGetToks dflags filename handle = do
   buf <- hGetStringBufferBlock handle blockSize
   unsafeInterleaveIO $ lazyLexBuf handle (pragState dflags buf loc) False
  where
-  loc  = mkSrcLoc (mkFastString filename) 1 0
+  loc  = mkSrcLoc (mkFastString filename) 1 1
 
   lazyLexBuf :: Handle -> PState -> Bool -> IO [Located Token]
   lazyLexBuf handle state eof = do
@@ -141,7 +141,7 @@ lazyGetToks dflags filename handle = do
 getToks :: DynFlags -> FilePath -> StringBuffer -> [Located Token]
 getToks dflags filename buf = lexAll (pragState dflags buf loc)
  where
-  loc  = mkSrcLoc (mkFastString filename) 1 0
+  loc  = mkSrcLoc (mkFastString filename) 1 1
 
   lexAll state = case unP (lexer return) state of
                    POk _      t@(L _ ITeof) -> [t]
index e0d81b7..9c21d0a 100644 (file)
@@ -183,7 +183,7 @@ hscParse mod_summary = do
             Just b  -> return b
             Nothing -> liftIO $ hGetStringBuffer src_filename
 
-   let loc  = mkSrcLoc (mkFastString src_filename) 1 0
+   let loc  = mkSrcLoc (mkFastString src_filename) 1 1
 
    case unP parseModule (mkPState buf loc dflags) of
      PFailed span err ->
@@ -984,7 +984,7 @@ hscParseThing parser dflags str
 
       buf <- liftIO $ stringToStringBuffer str
 
-      let loc  = mkSrcLoc (fsLit "<interactive>") 1 0
+      let loc  = mkSrcLoc (fsLit "<interactive>") 1 1
 
       case unP parser (mkPState buf loc dflags) of
 
index e131e96..dca51e4 100644 (file)
@@ -1135,7 +1135,7 @@ do_layout_left span _buf _len = do
 setLine :: Int -> Action
 setLine code span buf len = do
   let line = parseUnsignedInteger buf len 10 octDecDigit
-  setSrcLoc (mkSrcLoc (srcSpanFile span) (fromIntegral line - 1) 0)
+  setSrcLoc (mkSrcLoc (srcSpanFile span) (fromIntegral line - 1) 1)
        -- subtract one: the line number refers to the *following* line
   _ <- popLexState
   pushLexState code
index 9068502..4cd637f 100644 (file)
@@ -2012,6 +2012,6 @@ sL span a = span `seq` a `seq` L span a
 fileSrcSpan :: P SrcSpan
 fileSrcSpan = do 
   l <- getSrcLoc; 
-  let loc = mkSrcLoc (srcLocFile l) 1 0;
+  let loc = mkSrcLoc (srcLocFile l) 1 1;
   return (mkSrcSpan loc loc)
 }