hasktags enhancements ? How to contribute?

Marc Weber marco-oweber at gmx.de
Fri Jul 24 16:47:03 EDT 2009


Hi,

more than a year ago I enhanced hasktags. Now I had another look at my
code ensuring that it finds at least as many tags as the hackage
implementation does. It also adds a small test suite ensuring progress.

So let me know how well it works for you. If some tags aren't found send
me a test case so that I can add it to the test suite.

Where to get it from:  darcs get http://mawercer.de/~marc/my-hasktags

So what's different ?
- it finds more tags (see details below)
- it adds tag kinds (vim only)
   Example:
    SpacingCombiningMark	./2/testcase2.hs	154;"	cons
    Surrogate	./2/testcase2.hs	175;"	cons
    TitlecaseLetter	./2/testcase2.hs	150;"	cons
    UppercaseLetter	./2/testcase2.hs	148;"	d
    digitToInt	./2/testcase2.hs	131;"	ft
    digitToInt	./2/testcase2.hs	132;"	fi

  cons = contstructor
  ft = funtion type
  fi = function implementation
  m = module
  
- adds the flag --ignore-close-implementation
  eg if you have

    abc,def :: Int
    
    abc = 7
    
    {- 20 line comment 
    .. -}
    def = 8

  abc is added once (because the type definition and the implementation
  is very close) but def is added twice because you may want to jump to
  either one directly. That's important because :tjump (vim) won't
  bother you asking you which one to take. So the list of tags is
  shorter in general.


details about finding more tags:
a) it finds more tags -> [1]
  Example (by testcase)
  1)
    module Main where
      import Text.JSON

      func = ...
    
    using this strange indentation the hackage hasktags fails horribly (test case 1)
 
  2) from Data.Char
    #ifndef __GLASGOW_HASKELL__
    isAsciiUpper, isAsciiLower :: Char -> Bool
    isAsciiLower c          =  c >= 'a' && c <= 'z'
    isAsciiUpper c          =  c >= 'A' && c <= 'Z'
    #endif

    this isAsciiUpper isn't found by the hackage version for some reason
  
  4) the basic rootLoggerName isn't found!
    module System.Log.Logger

    rootLoggerName = ""

  5) Saying those aren't found isn't quite true. the hackage version
    just doesn't remove the parenthesis and adds (@?) to the tag file.

  8) ABCD isn't found because of this parenthesis
    class (Show a) => (ABCD a) where

    Again (ABCD is found instead.


You can test this yourself by running my testsuite (cd testcases; sh test.sh)

Marc Weber


More information about the Libraries mailing list