[Haskell-cafe] which tags program should I use?

Erik Hesselink hesselink at gmail.com
Mon Sep 26 21:28:56 CEST 2011


I use hothasktags [1] which works very well. The only problems are
sometimes with obscure extensions, where haskell-src-exts (which
hothasktags uses) can't parse the file, but that happens very rarely.

Regarding speed: it takes 2-3 s on about 250 source files totaling
about 25000 lines on my laptop.

Regards,

Erik

[1] https://github.com/luqui/hothasktags/

On Sun, Sep 25, 2011 at 15:41, Henry Laxen <nadine.and.henry at pobox.com> wrote:
> Dear Group,
>
> I have a simple question, that as far as I can tell, has never really
> been well answered.  I would like to generate TAGS files for haskell
> source.  Reading the http://www.haskell.org/haskellwiki/Tags page
> suggests using :etags in GHCI or hasktags, or gasbag.  Of the three,
> hasktags comes closest to "working" but it has (for me) a major
> inconvenience, namely it finds both function definitions and type
> signatures, resulting in two TAGS entries such as:
>
> ./Main.hs,63
> module Main where 6,7
> main :: 24,25
> main = 25,26
>
> Now when I do an emacs find-tag (I use icicles) I will always have to
> choose which tag I want to visit, and the completion buffer contains
> something like:
>
> main ::
> hs/Main.hs
>
> main =
> hs/Main.hs
>
>
> Granted, this is a minor (and very specialized) complaint, but if
> hasktags were to select only ONE of either the type signature (my
> first choice) or the function definition, (if no type signature) this
> annoyance would disappear.
>
> I also tried using etags, which I think would work, but it seems to
> have one killer bug (feature), namely that it dies if it finds an
> uninterpreted import:
>
>  when (not is_interpreted) $
>    let mName = GHC.moduleNameString (GHC.moduleName m) in
>    ghcError (CmdLineError ("module '" ++ mName ++ "' is not interpreted"))
>
> I think it would work much better if it just warned you, instead of
> dying.  This makes it unusable any time you import something
> precompiled.
>
> Now some looking at the README of hasktags leads me to:
>
> "In the past this tool was distributed with ghc. I forked and added some
> features.  hasktags itself was moved out of the ghc repository. Then I only
> verified that my fork finds at least as much tags as the one forked by
> Igloo."
>
> That makes me feel a little queasy.
>
> A google search for hasktags igloo turns up
> http://hackage.haskell.org/trac/ghc/ticket/1508
> whose title is "hasktags program needs replacement"
> which makes me feel even more queasy.
>
> So I guess my question is, what are us disciples of "the one true
> editor" to do?  Thanks in advance for you sage advice.
>
> Best wishes,
> Henry Laxen
>
>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



More information about the Haskell-Cafe mailing list