Tweak hasktags to cope with abc::def correctly
[ghc-hetmet.git] / utils / hasktags / HaskTags.hs
1 module Main where
2 import Char
3 import List
4 import IO
5 import System.Environment
6 import System.Console.GetOpt
7 import System.Exit
8
9
10 -- search for definitions of things 
11 -- we do this by looking for the following patterns:
12 -- data XXX = ...      giving a datatype location
13 -- newtype XXX = ...   giving a newtype location
14 -- bla :: ...          giving a function location
15 --
16 -- by doing it this way, we avoid picking up local definitions
17 --              (whether this is good or not is a matter for debate)
18 --
19
20 -- We generate both CTAGS and ETAGS format tags files
21 -- The former is for use in most sensible editors, while EMACS uses ETAGS
22
23
24 main :: IO ()
25 main = do
26         progName <- getProgName
27         args <- getArgs
28         let usageString = "Usage: " ++ progName ++ " [OPTION...] [files...]"
29         let (modes, filenames, errs) = getOpt Permute options args
30         if errs /= [] || elem Help modes || filenames == []
31          then do
32            putStr $ unlines errs 
33            putStr $ usageInfo usageString options
34            exitWith (ExitFailure 1)
35          else return ()
36         let mode = getMode (Append `delete` modes)
37         let openFileMode = if elem Append modes
38                            then AppendMode
39                            else WriteMode
40         filedata <- mapM findthings filenames
41         if mode == BothTags || mode == CTags
42          then do 
43            ctagsfile <- openFile "tags" openFileMode
44            writectagsfile ctagsfile filedata
45            hClose ctagsfile
46          else return ()
47         if mode == BothTags || mode == ETags 
48          then do
49            etagsfile <- openFile "TAGS" openFileMode
50            writeetagsfile etagsfile filedata
51            hClose etagsfile
52          else return ()
53
54 -- | getMode takes a list of modes and extract the mode with the
55 --   highest precedence.  These are as follows: Both, CTags, ETags
56 --   The default case is Both.
57 getMode :: [Mode] -> Mode
58 getMode [] = BothTags
59 getMode [x] = x
60 getMode (x:xs) = max x (getMode xs)
61
62
63 data Mode = ETags | CTags | BothTags | Append | Help deriving (Ord, Eq, Show)
64
65 options :: [OptDescr Mode]
66 options = [ Option "c" ["ctags"]
67             (NoArg CTags) "generate CTAGS file (ctags)"
68           , Option "e" ["etags"]
69             (NoArg ETags) "generate ETAGS file (etags)"
70           , Option "b" ["both"]
71             (NoArg BothTags) ("generate both CTAGS and ETAGS")
72           , Option "a" ["append"]
73             (NoArg Append) ("append to existing CTAGS and/or ETAGS file(s)")
74           , Option "h" ["help"] (NoArg Help) "This help"
75           ]
76
77 type FileName = String
78
79 type ThingName = String
80
81 -- The position of a token or definition
82 data Pos = Pos 
83                 FileName        -- file name
84                 Int                     -- line number 
85                 Int             -- token number
86                 String          -- string that makes up that line
87         deriving Show
88
89 -- A definition we have found
90 data FoundThing = FoundThing ThingName Pos
91         deriving Show
92
93 -- Data we have obtained from a file
94 data FileData = FileData FileName [FoundThing]
95
96 data Token = Token String Pos
97         deriving Show
98
99
100 -- stuff for dealing with ctags output format
101
102 writectagsfile :: Handle -> [FileData] -> IO ()
103 writectagsfile ctagsfile filedata = do
104         let things = concat $ map getfoundthings filedata
105         mapM_ (\x -> hPutStrLn ctagsfile $ dumpthing x) things
106
107 getfoundthings :: FileData -> [FoundThing]
108 getfoundthings (FileData filename things) = things
109
110 dumpthing :: FoundThing -> String
111 dumpthing (FoundThing name (Pos filename line _ _)) = 
112         name ++ "\t" ++ filename ++ "\t" ++ (show $ line + 1)
113
114
115 -- stuff for dealing with etags output format
116
117 writeetagsfile :: Handle -> [FileData] -> IO ()
118 writeetagsfile etagsfile filedata = do
119         mapM_ (\x -> hPutStr etagsfile $ e_dumpfiledata x) filedata
120
121 e_dumpfiledata :: FileData -> String
122 e_dumpfiledata (FileData filename things) = 
123         "\x0c\n" ++ filename ++ "," ++ (show thingslength) ++ "\n" ++ thingsdump
124         where 
125                 thingsdump = concat $ map e_dumpthing things 
126                 thingslength = length thingsdump
127
128 e_dumpthing :: FoundThing -> String
129 e_dumpthing (FoundThing name (Pos filename line token fullline)) =
130         (concat $ take (token + 1) $ spacedwords fullline) 
131         ++ "\x7f" ++ (show line) ++ "," ++ (show $ line+1) ++ "\n"
132         
133         
134 -- like "words", but keeping the whitespace, and so letting us build
135 -- accurate prefixes    
136         
137 spacedwords :: String -> [String]
138 spacedwords [] = []
139 spacedwords xs = (blanks ++ wordchars):(spacedwords rest2)
140         where 
141                 (blanks,rest) = span Char.isSpace xs
142                 (wordchars,rest2) = span (\x -> not $ Char.isSpace x) rest
143         
144         
145 -- Find the definitions in a file       
146         
147 findthings :: FileName -> IO FileData
148 findthings filename = do
149     text <- readFile filename
150     evaluate text -- forces evaluation of text
151                   -- too many files were being opened otherwise since
152                   -- readFile is lazy
153     let aslines = lines text
154     let wordlines = map mywords aslines
155     let noslcoms = map stripslcomments wordlines
156     let tokens = concat $ zipWith3 (withline filename) noslcoms aslines [0 ..]
157     let nocoms = stripblockcomments tokens
158     return $ FileData filename $ findstuff nocoms
159   where evaluate [] = return ()
160         evaluate (c:cs) = c `seq` evaluate cs
161         -- my words is mainly copied from Data.List.
162         -- difference abc::def is split into three words instead of one.
163         -- We should really be lexing Haskell properly here rather
164         -- than using hacks like this. In the future we expect hasktags
165         -- to be replaced by something using the GHC API.
166         mywords :: String -> [String]
167         mywords (':':':':xs) = "::" : mywords xs
168         mywords s =  case dropWhile isSpace s of
169                          "" -> []
170                          s' -> w : mywords s''
171                              where (w, s'') = myBreak s'
172                                    myBreak [] = ([],[])
173                                    myBreak (':':':':xs) = ([], "::"++xs)
174                                    myBreak (' ':xs) = ([],xs);
175                                    myBreak (x:xs) = let (a,b) = myBreak xs
176                                                     in  (x:a,b)
177 -- Create tokens from words, by recording their line number
178 -- and which token they are through that line
179
180 withline :: FileName -> [String] -> String -> Int -> [Token]            
181 withline filename words fullline i = 
182         zipWith (\w t -> Token w (Pos filename i t fullline)) words $ [0 ..]
183
184 -- comments stripping
185
186 stripslcomments :: [String] -> [String]
187 stripslcomments ("--":xs) = []
188 stripslcomments (x:xs) = x : stripslcomments xs 
189 stripslcomments [] = []
190
191 stripblockcomments :: [Token] -> [Token]
192 stripblockcomments ((Token "\\end{code}" _):xs) = afterlitend xs
193 stripblockcomments ((Token "{-" _):xs) = afterblockcomend xs
194 stripblockcomments (x:xs) = x:stripblockcomments xs
195 stripblockcomments [] = []
196
197 afterlitend2 :: [Token] -> [Token]
198 afterlitend2 (x:xs) = afterlitend xs
199 afterlitend2 [] = []
200
201 afterlitend :: [Token] -> [Token]
202 afterlitend ((Token "\\begin{code}" _):xs) = xs
203 afterlitend (x:xs) = afterlitend xs
204 afterlitend [] = []
205
206 afterblockcomend :: [Token] -> [Token]
207 afterblockcomend ((Token token _):xs) | contains "-}" token = xs
208                                                 | otherwise = afterblockcomend xs
209 afterblockcomend [] = []
210
211
212 -- does one string contain another string
213
214 contains :: Eq a => [a] -> [a] -> Bool
215 contains sub full = any (isPrefixOf sub) $ tails full 
216
217 ints :: Int -> [Int]
218 ints i = i:(ints $ i+1)
219
220
221 -- actually pick up definitions
222
223 findstuff :: [Token] -> [FoundThing]
224 findstuff ((Token "data" _):(Token name pos):xs) = 
225         FoundThing name pos : (getcons xs) ++ (findstuff xs)
226 findstuff ((Token "newtype" _):(Token name pos):xs) = 
227         FoundThing name pos : findstuff xs
228 findstuff ((Token "type" _):(Token name pos):xs) = 
229         FoundThing name pos : findstuff xs
230 findstuff ((Token name pos):(Token "::" _):xs) = 
231         FoundThing name pos : findstuff xs
232 findstuff (x:xs) = findstuff xs
233 findstuff [] = []
234
235
236 -- get the constructor definitions, knowing that a datatype has just started
237
238 getcons :: [Token] -> [FoundThing]
239 getcons ((Token "=" _):(Token name pos):xs) = 
240         FoundThing name pos : getcons2 xs
241 getcons (x:xs) = getcons xs
242 getcons [] = []
243
244
245 getcons2 ((Token "=" _):xs) = []
246 getcons2 ((Token "|" _):(Token name pos):xs) = 
247         FoundThing name pos : getcons2 xs
248 getcons2 (x:xs) = getcons2 xs
249 getcons2 [] = []
250