Use 'GhcMonad' in ghci/GhciTags.
[ghc-hetmet.git] / compiler / ghci / GhciTags.hs
index a974c01..b53a56f 100644 (file)
@@ -1,18 +1,11 @@
 -----------------------------------------------------------------------------
 --
--- GHCi's :ctags and :etags commands 
+-- GHCi's :ctags and :etags commands
 --
 -- (c) The GHC Team 2005-2007
 --
 -----------------------------------------------------------------------------
 
-{-# 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
-
 module GhciTags (createCTagsFileCmd, createETagsFileCmd) where
 
 import GHC
@@ -24,9 +17,10 @@ import Util
 -- into the GHC API instead
 import Name (nameOccName)
 import OccName (pprOccName)
+import MonadUtils
 
 import Data.Maybe
-import Control.Exception
+import Panic
 import Data.List
 import Control.Monad
 import System.IO
@@ -47,8 +41,7 @@ data TagsKind = ETags | CTags
 
 ghciCreateTagsFile :: TagsKind -> FilePath -> GHCi ()
 ghciCreateTagsFile kind file = do
-  session <- getSession
-  io $ createTagsFile session kind file
+  createTagsFile kind file
 
 -- ToDo: 
 --     - remove restriction that all modules must be interpreted
@@ -58,22 +51,22 @@ ghciCreateTagsFile kind file = do
 --     - extract createTagsFile so it can be used from the command-line
 --       (probably need to fix first problem before this is useful).
 --
-createTagsFile :: Session -> TagsKind -> FilePath -> IO ()
-createTagsFile session tagskind tagFile = do
-  graph <- GHC.getModuleGraph session
+createTagsFile :: TagsKind -> FilePath -> GHCi ()
+createTagsFile tagskind tagFile = do
+  graph <- GHC.getModuleGraph
   let ms = map GHC.ms_mod graph
       tagModule m = do 
-        is_interpreted <- GHC.moduleIsInterpreted session m
+        is_interpreted <- GHC.moduleIsInterpreted m
         -- should we just skip these?
         when (not is_interpreted) $
-          throwDyn (CmdLineError ("module '" 
+          ghcError (CmdLineError ("module '" 
                                 ++ GHC.moduleNameString (GHC.moduleName m)
                                 ++ "' is not interpreted"))
-        mbModInfo <- GHC.getModuleInfo session m
+        mbModInfo <- GHC.getModuleInfo m
         unqual <-
           case mbModInfo of
              Just minf -> do
-                mb_print_unqual <- GHC.mkPrintUnqualifiedForModule session minf
+                mb_print_unqual <- GHC.mkPrintUnqualifiedForModule minf
                 return (fromMaybe GHC.alwaysQualify mb_print_unqual)
              Nothing ->
                 return GHC.alwaysQualify
@@ -82,9 +75,9 @@ createTagsFile session tagskind tagFile = do
           _            -> return []
 
   mtags <- mapM tagModule ms
-  either_res <- collateAndWriteTags tagskind tagFile $ concat mtags
+  either_res <- liftIO $ collateAndWriteTags tagskind tagFile $ concat mtags
   case either_res of
-    Left e  -> hPutStrLn stderr $ ioeGetErrorString e
+    Left e  -> liftIO $ hPutStrLn stderr $ ioeGetErrorString e
     Right _ -> return ()
 
 listTags :: PrintUnqualified -> GHC.ModuleInfo -> [TagInfo]
@@ -120,27 +113,26 @@ collateAndWriteTags ETags file tagInfos = do -- etags style, Emacs/XEmacs
   tagGroups <- mapM tagFileGroup groups 
   IO.try (writeFile file $ concat tagGroups)
   where
-    tagFileGroup group@[] = throwDyn (CmdLineError "empty tag file group??")
+    tagFileGroup [] = ghcError (CmdLineError "empty tag file group??")
     tagFileGroup group@((_,fileName,_,_):_) = do
       file <- readFile fileName -- need to get additional info from sources..
       let byLine (_,_,l1,_) (_,_,l2,_) = l1 <= l2
           sortedGroup = sortLe byLine group
           tags = unlines $ perFile sortedGroup 1 0 $ lines file
       return $ "\x0c\n" ++ fileName ++ "," ++ show (length tags) ++ "\n" ++ tags
-    perFile (tagInfo@(tag,file,lNo,colNo):tags) count pos (line:lines) | lNo>count =
-      perFile (tagInfo:tags) (count+1) (pos+length line) lines
-    perFile (tagInfo@(tag,file,lNo,colNo):tags) count pos lines@(line:_) | lNo==count =
-      showETag tagInfo line pos : perFile tags count pos lines
-    perFile tags count pos lines = []
+    perFile (tagInfo@(_tag, _file, lNo, _colNo):tags) count pos lines@(line:lines')
+     | lNo >  count = perFile (tagInfo:tags) (count+1) (pos+length line) lines'
+     | lNo == count = showETag tagInfo line pos : perFile tags count pos lines
+    perFile _ _ _ _ = []
 
 -- simple ctags format, for Vim et al
 showTag :: TagInfo -> String
-showTag (tag,file,lineNo,colNo)
+showTag (tag, file, lineNo, _colNo)
     =  tag ++ "\t" ++ file ++ "\t" ++ show lineNo
 
 -- etags format, for Emacs/XEmacs
 showETag :: TagInfo -> String -> Int -> String
-showETag (tag,file,lineNo,colNo) line charPos
+showETag (tag, _file, lineNo, colNo) line charPos
     =  take colNo line ++ tag
     ++ "\x7f" ++ tag
     ++ "\x01" ++ show lineNo