Tools__TagList.st
author Claus Gittinger <cg@exept.de>
Fri, 06 May 2011 10:36:33 +0200
changeset 9891 67a9308a6109
child 9915 923eae65fc70
permissions -rw-r--r--
initial checkin

"
 COPYRIGHT (c) 2002 by eXept Software AG 
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
"{ Package: 'stx:libtool' }"

"{ NameSpace: Tools }"

List subclass:#TagList
	instanceVariableNames:'rawList filteredList filter sortCriteria groupBy showOnly
		hideStatic hideStructMembers hideClasses hideMethods hideDefines
		hideTypedefs hideVariables hideStructures hideFunctions
		hideFunctionProtoTypes hideJavaClasses hideJavaMethods
		hideJavaInterfaces hideJavaFields hideJavaPackages hideLispMacros
		hideLispEvaluations hideLispMethods hideLispConstants
		hideLocalLabels hideDataLabels hideTextLabels tagTypesPresent
		hidePythonClasses hidePythonMethods hidePythonFunctions
		hideOzClasses hideOzMethods hideOzFunctions hideHTMLTextArea
		hideHTMLInput hideHTMLTable hideHTMLScript target
		usingDefaultCTags ctagsCommand ctagsIsExCtags ctagsIsExCtags5x'
	classVariableNames:'Sorted CachedTagListsPerFile DefaultSortCriteria DefaultShowOnly
		TagsSuffixes DefaultGroupBy'
	poolDictionaries:''
	category:'Interface-Tools-File-Tags'
!

!TagList class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2002 by eXept Software AG 
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.


"
! !

!TagList class methodsFor:'accessing'!

tagsSuffixes
"flush with:
TagsSuffixes := nil
"
    TagsSuffixes notNil ifTrue:[
        ^ TagsSuffixes
    ].
    TagsSuffixes := IdentityDictionary new.

    TagsSuffixes at:#'text/asm'                 put:#( 's' 'asm' ).
    TagsSuffixes at:#'text/c'                   put:#( 'c' 'h' 'ci' 'hi' 'sc').
    TagsSuffixes at:#'text/cpp'                 put:#( 'cc' 'cpp' 'cxx' 'c++' 'hxx' 'hpp' 'h++').
    TagsSuffixes at:#'text/eiffel'              put:#( 'e' 'eif' ).
    TagsSuffixes at:#'text/fortran'             put:#( 'f' 'for' 'ftn' 'f77' 'f90' ).
    TagsSuffixes at:#'text/html'                put:#( 'htm' 'html').
    TagsSuffixes at:#'text/java'                put:#( 'java' 'jav').
    TagsSuffixes at:#'text/javaScript'          put:#( 'js' ).
    TagsSuffixes at:#'text/javascript'          put:#( 'js' ).
    TagsSuffixes at:#'application/x-javascript' put:#( 'js' ).
    TagsSuffixes at:#'text/make'                put:#( 'makefile' 'make.proto' 'makefile.*' '*.mak' '*.bpr').
    TagsSuffixes at:#'text/prolog'              put:#( 'pl' ).
    TagsSuffixes at:#'text/python'              put:#( 'py' ).
    TagsSuffixes at:#'text/php'                 put:#( 'php' ).
    TagsSuffixes at:#'text/lisp'                put:#( 'lisp' 'el' 'lsp' 'cl').
    TagsSuffixes at:#'text/lisp-arc'            put:#( 'arc' ).
    TagsSuffixes at:#'text/scheme'              put:#( 'scm' 'ss' 'brg').
    TagsSuffixes at:#'text/oz'                  put:#( 'oz').
    TagsSuffixes at:#'text/smalltalk'           put:#( 'st' ).
    TagsSuffixes at:#'text/tcl'                 put:#( 'tcl' ).
    TagsSuffixes at:#'text/ruby'                put:#( 'rb' ).
    TagsSuffixes at:#'text/yacc'                put:#( 'y' ).
    ^ TagsSuffixes

    "Modified: / 20-04-2011 / 19:27:53 / cg"
! !

!TagList class methodsFor:'defaults'!

arcLispSuffixes
    "returns a list of supported arc-lisp-suffixes"

    ^ self tagsSuffixes at:#'text/lisp-arc'
!

assemblerSuffixes
    "returns a list of supported assembler-suffixes"

    ^ self tagsSuffixes at:#'text/asm'
!

cPlusPlusSuffixes
    "returns a list of supported c-suffixes"

    ^ self tagsSuffixes at:#'text/cpp'
!

cSuffixes
    "returns a list of supported c-suffixes"

    ^ self tagsSuffixes at:#'text/c'
!

commonLispSuffixes
    "returns a list of supported common-lisp-suffixes"

    ^ self tagsSuffixes at:#'text/lisp'
!

eiffelSuffixes
    "returns a list of supported eiffel-suffixes
    "
    ^ self tagsSuffixes at:#'text/eiffel'
!

fortranSuffixes
    "returns a list of supported fortran-suffixes
    "
    ^ self tagsSuffixes at:#'text/fortran'
!

htmlSuffixes
    "returns a list of supported html-suffixes
    "
    ^ self tagsSuffixes at:#'text/html'

    "Created: / 20-04-2011 / 19:03:39 / cg"
!

isTagSearchableSuffix:aSuffix
    "returns true, if aSuffix looks ok for ctags
    "
    self tagsSuffixes keysAndValuesDo:[:tag :suffixes |
        (suffixes includes:aSuffix) ifTrue:[^ true].
    ].
"/    (self cSuffixes includes:aSuffix) ifTrue:[^ true].
"/    (self javaSuffixes includes:aSuffix) ifTrue:[^ true].
"/    (self fortranSuffixes includes:aSuffix) ifTrue:[^ true].
"/    (self eiffelSuffixes includes:aSuffix) ifTrue:[^ true].
"/    (self commonLispSuffixes includes:aSuffix) ifTrue:[^ true].
"/    (self schemeSuffixes includes:aSuffix) ifTrue:[^ true].
    ^ false
!

javaScriptSuffixes
    "returns a list of supported javaScript-suffixes"

    ^ self tagsSuffixes at:#'text/javaScript'

    "Created: / 28-06-2010 / 12:44:58 / cg"
!

javaSuffixes
    "returns a list of supported java-suffixes
    "
    ^ self tagsSuffixes at:#'text/java'
!

makeFilePatterns
    "returns a list of makefile match patterns
    "
    ^ self tagsSuffixes at:#'text/make'
!

ozSuffixes
    "returns a list of supported oz-suffixes
    "
    ^ self tagsSuffixes at:#'text/oz'
!

phpSuffixes
    "returns a list of supported php-suffixes"

    ^ self tagsSuffixes at:#'text/php'
!

prologSuffixes
    "returns a list of supported prolog-suffixes
    "
    ^ self tagsSuffixes at:#'text/prolog'
!

pythonSuffixes
    "returns a list of supported python-suffixes
    "
    ^ self tagsSuffixes at:#'text/python'
!

rubySuffixes
    "returns a list of supported ruby-suffixes
    "
    ^ self tagsSuffixes at:#'text/ruby'
!

schemeSuffixes
    "returns a list of supported scheme-lisp-suffixes
    "
    ^ self tagsSuffixes at:#'text/scheme'
!

smalltalkSuffixes
    "returns a list of supported smalltalk-suffixes
    "
    ^ self tagsSuffixes at:#'text/smalltalk'
!

tclSuffixes
    "returns a list of supported tcl-suffixes
    "
    ^ self tagsSuffixes at:#'text/tcl'
!

yaccSuffixes
    "returns a list of supported yacc-suffixes
    "
    ^ self tagsSuffixes at:#'text/yacc'
! !

!TagList class methodsFor:'queries'!

isArcLispSuffix:suffix
    ^ self isSuffix:suffix in:self arcLispSuffixes
!

isAssemblerSuffix:suffix
    ^ self isSuffix:suffix in:self assemblerSuffixes
!

isCPlusPlusSuffix:suffix
    ^ self isSuffix:suffix in:self cPlusPlusSuffixes
!

isCSuffix:suffix
    ^ self isSuffix:suffix in:self cSuffixes
!

isCommonLispSuffix:suffix
    ^ self isSuffix:suffix in:self commonLispSuffixes
!

isEiffelSuffix:suffix
    ^ self isSuffix:suffix in:self eiffelSuffixes
!

isFortranSuffix:suffix
    ^ self isSuffix:suffix in:self fortranSuffixes
!

isHTMLSuffix:suffix
    ^ self isSuffix:suffix in:self htmlSuffixes

    "Created: / 20-04-2011 / 19:03:26 / cg"
!

isJavaScriptSuffix:suffix
    ^ self isSuffix:suffix in:self javaScriptSuffixes

    "Created: / 28-06-2010 / 12:44:47 / cg"
!

isJavaSuffix:suffix
    ^ self isSuffix:suffix in:self javaSuffixes
!

isLispSuffix:suffix
    ^ (self isCommonLispSuffix:suffix) 
    or:[(self isSchemeSuffix:suffix)
    or:[self isArcLispSuffix:suffix]]
!

isMakefileName:fileName
    |lcName|

    lcName := fileName asFilename baseName asLowercase.
    self makeFilePatterns do:[:aPattern |
        (aPattern match:lcName) ifTrue:[ ^ true ].
    ].
    ^ false
!

isOzSuffix:suffix
    ^ self isSuffix:suffix in:self ozSuffixes
!

isPhpSuffix:suffix
    ^ self isSuffix:suffix in:self phpSuffixes
!

isPrologSuffix:suffix
    ^ self isSuffix:suffix in:self prologSuffixes
!

isPythonSuffix:suffix
    ^ self isSuffix:suffix in:self pythonSuffixes
!

isRubySuffix:suffix
    ^ self isSuffix:suffix in:self rubySuffixes
!

isSchemeSuffix:suffix
    ^ self isSuffix:suffix in:self schemeSuffixes
!

isSmalltalkSuffix:suffix
    ^ self isSuffix:suffix in:self smalltalkSuffixes
!

isTCLSuffix:suffix
    ^ self isSuffix:suffix in:self tclSuffixes
!

isYaccSuffix:suffix
    ^ self isSuffix:suffix in:self yaccSuffixes
! !

!TagList class methodsFor:'queries basic'!

isSuffix:suffix in:patterns
    |lcSuffix|

    lcSuffix := suffix asLowercase.
    ^ patterns contains:[:pattern | pattern match:lcSuffix].
!

tagMimeTypeForFile:aFile
    "returns the tag-mimetype for a file or nil
    "
    |suff file list name mimeMake|

    aFile isNil ifTrue:[^ nil].

    file := aFile asFilename.
    suff := aFile asFilename suffix.

    suff size ~~ 0 ifTrue:[
        suff := suff asLowercase.

        (suff = 'bak' or:[suff = 'sav']) ifTrue:[
            file := file asFilename withoutSuffix.
            suff := file suffix.
            suff size ~~ 0 ifTrue:[
                suff := suff asLowercase
            ]
        ]
    ].
    list := self tagsSuffixes.

    " hack to test for make-file patterns "
    name := file baseName asLowercase.
    mimeMake := #'text/make'.

    ((list at:mimeMake) contains:[:pattern | pattern match:name]) ifTrue:[
        ^ mimeMake
    ].

    self tagsSuffixes keysAndValuesDo:[:mimeType :suffixes|
        (suffixes includes:suff) ifTrue:[ ^ mimeType ]
    ].
    ^ nil
! !

!TagList class methodsFor:'tag generation'!

cachedTagsFromFile:aFilename in:aTempDirectory
    "retrieve a cached tagList for a file"

    |tagList cached fileTime suffix|

    fileTime := aFilename modificationTime.

    CachedTagListsPerFile isNil ifTrue:[
        CachedTagListsPerFile := Dictionary new.
    ].
    cached := CachedTagListsPerFile at:aFilename ifAbsent:nil.
    cached notNil ifTrue:[
        fileTime > cached tagTimestamp ifFalse:[
            ^ cached tagList
        ]
    ].
    suffix := aFilename suffix.

"/    ((self isCSuffix:suffix) 
"/    or:[(self isJavaSuffix:suffix)
"/    or:[(self isFortranSuffix:suffix)
"/    or:[(self isEiffelSuffix:suffix)]]])
"/    ifFalse:[
"/        ^ #()
"/    ].
    tagList := self new.
    tagList showOnly:nil.
    tagList fromFile:aFilename in:aTempDirectory.

    CachedTagListsPerFile at:aFilename put:(CachedTags new tagList:tagList; tagTimestamp:fileTime; yourself).
    ^ tagList

    "Modified: / 07-06-2010 / 12:13:25 / cg"
!

cachedTagsFromFile:aFilename in:aTempDirectory buildTargetHandler:aTargetHandler remote:aBoolean
    "retrieve a cached tagList for a file"

    ^ self cachedTagsFromFile:aFilename in:aTempDirectory.
!

flushCachedTags
    CachedTagListsPerFile := nil

    "
     self flushCachedTags
    "
!

makeTargetTagsInFile:aMakefilePath
    "makefile tags:
     naive, q&d scan for lines ending with a colon
    "
    ^ self makeTargetTagsInFile:aMakefilePath filter:nil
!

makeTargetTagsInFile:aMakefilePath filter:showOnly
    "makefile tags:
     naive, q&d scan for lines ending with a colon
    "
    |targets|

    Tag autoload.

    targets := OrderedCollection new.
    aMakefilePath asFilename contents keysAndValuesDo:[:lnr :line |
        |idxColon idxAssign varName target|

        line size > 0 ifTrue:[
            line first isSeparator ifFalse:[
                (line startsWith:$#) ifFalse:[
                    idxAssign := line indexOf:$=.
                    idxAssign ~~ 0 ifTrue:[
                        showOnly ~~ #targets ifTrue:[
                            varName := line copyFrom:1 to:idxAssign - 1.
                            targets add:(Tag::TVariable 
                                            label:varName 
                                            pattern:('/^',varName,'=')
                                            type:nil
                                            lineNumber:lnr)
                        ]
                    ] ifFalse:[
                        idxColon := line indexOf:$:.
                        idxColon ~~ 0 ifTrue:[
                            target := line copyFrom:1 to:idxColon - 1.
                            "/ ignore macro-targets

                            (target includes:$$) ifFalse:[
                                (target startsWith:$.) ifFalse:[
                                    "/ normal targets
                                    targets add:(Tag::TMakeTarget 
                                                    label:target 
                                                    pattern:('/^',target,':')
                                                    type:nil
                                                    lineNumber:lnr)
                                ] ifTrue:[
                                    "/ rule-targets
                                    targets add:(Tag::TMakeRule 
                                                    label:target 
                                                    pattern:('/^',target,':')
                                                    type:nil
                                                    lineNumber:lnr)
                                ]
                            ] ifTrue:[
                                "/ rule-targets
                                targets add:(Tag::TMakeTarget 
                                                label:target 
                                                pattern:('/^',target,':')
                                                type:nil
                                                lineNumber:lnr)
                            ].
                        ]
                    ]
                ]
            ]
        ]
    ].
    ^ targets
! !

!TagList methodsFor:'accessing-filters'!

classesFunctionsAndVariablesOnly
    ^ showOnly == #classesFunctionsAndVariables

    "Modified: / 07-06-2010 / 14:18:09 / cg"
!

classesFunctionsAndVariablesOnly:aBoolean
    showOnly := nil.
    aBoolean ifTrue:[
        showOnly := DefaultShowOnly := #classesFunctionsAndVariables
    ].

    "Modified: / 05-05-2011 / 15:21:53 / cg"
!

classesOnly
    ^ showOnly == #classes

    "Modified: / 07-06-2010 / 14:18:12 / cg"
!

classesOnly:aBoolean
    showOnly := nil.
    aBoolean ifTrue:[
        showOnly := DefaultShowOnly := #classes
    ].

    "Modified: / 05-05-2011 / 15:21:56 / cg"
!

definesOnly
    ^ showOnly == #defines

    "Modified: / 07-06-2010 / 14:18:15 / cg"
!

definesOnly:aBoolean
    showOnly := nil.
    aBoolean ifTrue:[
        showOnly := DefaultShowOnly := #defines
    ].

    "Modified: / 05-05-2011 / 15:21:58 / cg"
!

filter:something
    (filter ? '') ~= (something ? '') ifTrue:[
        filter := something.       
        rawList notNil ifTrue:[
            self updateContentsFromRawList
        ].
    ].

    "Modified: / 05-05-2011 / 14:43:04 / cg"
!

functionsAndVariablesOnly
    ^ showOnly == #functionsAndVariables

    "Modified: / 07-06-2010 / 14:18:05 / cg"
!

functionsAndVariablesOnly:aBoolean
    showOnly := nil.
    aBoolean ifTrue:[
        showOnly := DefaultShowOnly := #functionsAndVariables
    ].

    "Modified: / 05-05-2011 / 15:22:01 / cg"
!

functionsOnly
    ^ showOnly == #functions

    "Modified: / 07-06-2010 / 14:17:54 / cg"
!

functionsOnly:aBoolean
    showOnly := nil.
    aBoolean ifTrue:[
        showOnly := DefaultShowOnly := #functions
    ].

    "Modified: / 05-05-2011 / 15:22:03 / cg"
!

hideClasses
    ^ hideClasses ? false
!

hideClasses:aBoolean
    hideClasses := aBoolean.

    "Modified: / 05-05-2011 / 15:22:08 / cg"
!

hideDataLabels
    ^ hideDataLabels ? false
!

hideDataLabels:aBoolean
    hideDataLabels := aBoolean.

    "Modified: / 05-05-2011 / 15:22:10 / cg"
!

hideDefines
    ^ hideDefines ? false
!

hideDefines:aBoolean
    hideDefines := aBoolean.

    "Modified: / 05-05-2011 / 15:22:12 / cg"
!

hideFunctionProtoTypes
    ^ hideFunctionProtoTypes ? false
!

hideFunctionProtoTypes:aBoolean
    hideFunctionProtoTypes := aBoolean.

    "Modified: / 05-05-2011 / 15:22:14 / cg"
!

hideFunctions
    ^ hideFunctions ? false
!

hideFunctions:aBoolean
    hideFunctions := aBoolean.

    "Modified: / 05-05-2011 / 15:22:18 / cg"
!

hideHTMLInput
    ^ hideHTMLInput ? false

    "Created: / 20-04-2011 / 19:01:04 / cg"
!

hideHTMLInput:aBoolean
    hideHTMLInput := aBoolean.

    "Created: / 20-04-2011 / 19:01:32 / cg"
    "Modified: / 05-05-2011 / 15:22:21 / cg"
!

hideHTMLScript
    ^ hideHTMLScript ? false

    "Created: / 20-04-2011 / 19:00:32 / cg"
!

hideHTMLScript:aBoolean
    hideHTMLScript := aBoolean.

    "Created: / 20-04-2011 / 19:01:32 / cg"
    "Modified: / 05-05-2011 / 15:22:23 / cg"
!

hideHTMLTable
    ^ hideHTMLTable ? false

    "Created: / 20-04-2011 / 19:01:23 / cg"
!

hideHTMLTable:aBoolean
    hideHTMLTable := aBoolean.

    "Created: / 20-04-2011 / 19:01:48 / cg"
    "Modified: / 05-05-2011 / 15:22:26 / cg"
!

hideHTMLTextArea
    ^ hideHTMLTextArea ? false

    "Created: / 20-04-2011 / 19:00:55 / cg"
!

hideHTMLTextArea:aBoolean
    hideHTMLTextArea := aBoolean.

    "Created: / 20-04-2011 / 19:01:58 / cg"
    "Modified: / 05-05-2011 / 15:22:28 / cg"
!

hideJavaClasses
    ^ hideJavaClasses ? false
!

hideJavaClasses:aBoolean
    hideJavaClasses := aBoolean.

    "Modified: / 05-05-2011 / 15:22:32 / cg"
!

hideJavaFields
    ^ hideJavaFields ? false
!

hideJavaFields:aBoolean
    hideJavaFields := aBoolean.

    "Modified: / 05-05-2011 / 15:22:34 / cg"
!

hideJavaInterfaces
    ^ hideJavaInterfaces ? false
!

hideJavaInterfaces:aBoolean
    hideJavaInterfaces := aBoolean.

    "Modified: / 05-05-2011 / 15:22:38 / cg"
!

hideJavaMethods
    ^ hideJavaMethods ? false
!

hideJavaMethods:aBoolean
    hideJavaMethods := aBoolean.

    "Modified: / 05-05-2011 / 15:22:40 / cg"
!

hideJavaPackages
    ^ hideJavaPackages ? false
!

hideJavaPackages:aBoolean
    hideJavaPackages := aBoolean.

    "Modified: / 05-05-2011 / 15:22:41 / cg"
!

hideLispConstants
    ^ hideLispConstants ? false
!

hideLispConstants:aBoolean
    hideLispConstants := aBoolean.

    "Modified: / 05-05-2011 / 15:22:46 / cg"
!

hideLispEvaluations
    ^ hideLispEvaluations ? false
!

hideLispEvaluations:aBoolean
    hideLispEvaluations := aBoolean.

    "Modified: / 05-05-2011 / 15:22:49 / cg"
!

hideLispMacros
    ^ hideLispMacros ? false
!

hideLispMacros:aBoolean
    hideLispMacros := aBoolean.

    "Modified: / 05-05-2011 / 15:22:50 / cg"
!

hideLispMethods
    ^ hideLispMethods ? false
!

hideLispMethods:aBoolean
    hideLispMethods := aBoolean.

    "Modified: / 05-05-2011 / 15:22:53 / cg"
!

hideLocalLabels
    ^ hideLocalLabels ? false
!

hideLocalLabels:aBoolean
    hideLocalLabels := aBoolean.

    "Modified: / 05-05-2011 / 15:22:54 / cg"
!

hideOzClasses
    ^ hideOzClasses ? false
!

hideOzClasses:aBoolean
    hideOzClasses := aBoolean.

    "Modified: / 05-05-2011 / 15:22:58 / cg"
!

hideOzFunctions
    ^ hideOzFunctions ? false
!

hideOzFunctions:aBoolean
    hideOzFunctions := aBoolean.

    "Modified: / 05-05-2011 / 15:23:00 / cg"
!

hideOzMethods
    ^ hideOzMethods ? false
!

hideOzMethods:aBoolean
    hideOzMethods := aBoolean.

    "Modified: / 05-05-2011 / 15:23:02 / cg"
!

hidePythonClasses
    ^ hidePythonClasses ? false
!

hidePythonClasses:aBoolean
    hidePythonClasses := aBoolean.

    "Modified: / 05-05-2011 / 15:23:05 / cg"
!

hidePythonFunctions
    ^ hidePythonFunctions ? false
!

hidePythonFunctions:aBoolean
    hidePythonFunctions := aBoolean.

    "Modified: / 05-05-2011 / 15:23:07 / cg"
!

hidePythonMethods
    ^ hidePythonMethods ? false
!

hidePythonMethods:aBoolean
    hidePythonMethods := aBoolean.

    "Modified: / 05-05-2011 / 15:23:09 / cg"
!

hideStatic
    ^ hideStatic ? false
!

hideStatic:aBoolean
    hideStatic := aBoolean.

    "Modified: / 05-05-2011 / 15:23:11 / cg"
!

hideStructMembers
    ^ hideStructMembers ? false
!

hideStructMembers:aBoolean
    hideStructMembers := aBoolean.

    "Modified: / 05-05-2011 / 15:23:15 / cg"
!

hideStructures
    ^ hideStructures ? false
!

hideStructures:aBoolean
    hideStructures := aBoolean.

    "Modified: / 05-05-2011 / 15:23:17 / cg"
!

hideTextLabels
    ^ hideTextLabels ? false
!

hideTextLabels:aBoolean
    hideTextLabels := aBoolean.

    "Modified: / 05-05-2011 / 15:23:19 / cg"
!

hideTypedefs
    ^ hideTypedefs ? false
!

hideTypedefs:aBoolean
    hideTypedefs := aBoolean.

    "Modified: / 05-05-2011 / 15:23:21 / cg"
!

hideVariables
    ^ hideVariables ? false
!

hideVariables:aBoolean
    hideVariables := aBoolean.

    "Modified: / 05-05-2011 / 15:23:23 / cg"
!

javaClassesAndMethodsOnly
    ^ showOnly == #javaClassesAndMethods

    "Modified: / 07-06-2010 / 14:18:25 / cg"
!

javaClassesAndMethodsOnly:aBoolean
    showOnly := nil.
    aBoolean ifTrue:[
        showOnly := DefaultShowOnly := #javaClassesAndMethods
    ].

    "Modified: / 05-05-2011 / 15:23:25 / cg"
!

javaClassesOnly
    ^ showOnly == #javaClasses

    "Modified: / 07-06-2010 / 14:18:28 / cg"
!

javaClassesOnly:aBoolean
    showOnly := nil.
    aBoolean ifTrue:[
        showOnly := DefaultShowOnly := #javaClasses
    ].

    "Modified: / 05-05-2011 / 15:23:29 / cg"
!

javaMethodsOnly
    ^ showOnly == #javaMethods

    "Modified: / 07-06-2010 / 14:18:30 / cg"
!

javaMethodsOnly:aBoolean
    showOnly := nil.
    aBoolean ifTrue:[
        showOnly := DefaultShowOnly := #javaMethods
    ].

    "Modified: / 05-05-2011 / 15:23:31 / cg"
!

macrosOnly
    ^ showOnly == #macros

    "Created: / 07-06-2010 / 12:09:22 / cg"
    "Modified: / 07-06-2010 / 14:18:33 / cg"
!

macrosOnly:aBoolean
    showOnly := nil.
    aBoolean ifTrue:[
        showOnly := DefaultShowOnly := #macros
    ].

    "Created: / 07-06-2010 / 12:09:34 / cg"
    "Modified: / 05-05-2011 / 15:23:33 / cg"
!

methodsOnly
    ^ showOnly == #methods

    "Created: / 07-06-2010 / 12:12:26 / cg"
    "Modified: / 07-06-2010 / 14:18:38 / cg"
!

methodsOnly:aBoolean
    showOnly := nil.
    aBoolean ifTrue:[
        showOnly := DefaultShowOnly := #methods
    ].

    "Created: / 07-06-2010 / 12:12:30 / cg"
    "Modified: / 05-05-2011 / 15:23:35 / cg"
!

ozClassesOnly
    ^ showOnly == #ozClasses

    "Modified: / 07-06-2010 / 14:18:41 / cg"
!

ozClassesOnly:aBoolean
    showOnly := nil.
    aBoolean ifTrue:[
        showOnly := DefaultShowOnly := #ozClasses
    ].

    "Modified: / 05-05-2011 / 15:23:38 / cg"
!

ozFunctionsOnly
    ^ showOnly == #ozFunctions

    "Modified: / 07-06-2010 / 14:18:44 / cg"
!

ozFunctionsOnly:aBoolean
    showOnly := nil.
    aBoolean ifTrue:[
        showOnly := DefaultShowOnly := #ozFunctions
    ].
    self updateContentsFromRawList.

    "Modified: / 05-05-2011 / 15:18:51 / cg"
!

ozMethodsOnly
    ^ showOnly == #ozMethods

    "Modified: / 07-06-2010 / 14:18:47 / cg"
!

ozMethodsOnly:aBoolean
    showOnly := nil.
    aBoolean ifTrue:[
        showOnly := DefaultShowOnly := #ozMethods
    ].

    "Modified: / 05-05-2011 / 15:23:44 / cg"
!

pythonClassesOnly
    ^ showOnly == #pythonClasses

    "Modified: / 07-06-2010 / 14:18:52 / cg"
!

pythonClassesOnly:aBoolean
    showOnly := nil.
    aBoolean ifTrue:[
        showOnly := DefaultShowOnly := #pythonClasses
    ].

    "Modified: / 05-05-2011 / 15:23:46 / cg"
!

pythonFunctionsOnly
    ^ showOnly == #pythonFunctions

    "Modified: / 07-06-2010 / 14:18:55 / cg"
!

pythonFunctionsOnly:aBoolean
    showOnly := nil.
    aBoolean ifTrue:[
        showOnly := DefaultShowOnly := #pythonFunctions
    ].

    "Modified: / 05-05-2011 / 15:23:48 / cg"
!

pythonMethodsOnly
    ^ showOnly == #pythonMethods

    "Modified: / 07-06-2010 / 14:18:58 / cg"
!

pythonMethodsOnly:aBoolean
    showOnly := nil.
    aBoolean ifTrue:[
        showOnly := DefaultShowOnly := #pythonMethods
    ].

    "Modified: / 05-05-2011 / 15:23:51 / cg"
!

showOnly
    tagTypesPresent == false ifTrue:[
        ^ nil    "/ showing everything
    ].
    ^ showOnly "? DefaultShowOnly"

    "Modified: / 20-06-2010 / 01:44:13 / cg"
!

showOnly:aSymbol
    showOnly := aSymbol

    "Modified: / 05-05-2011 / 15:23:55 / cg"
!

structsOnly
    ^ showOnly == #structs

    "Created: / 25-06-2010 / 10:42:27 / cg"
!

structsOnly:aBoolean
    showOnly := DefaultShowOnly := nil.
    aBoolean ifTrue:[
        showOnly := "DefaultShowOnly :=" #structs
    ].

    "Created: / 25-06-2010 / 10:42:39 / cg"
    "Modified: / 05-05-2011 / 15:23:58 / cg"
!

targetsOnly
    ^ showOnly == #targets

    "Modified: / 07-06-2010 / 14:19:03 / cg"
!

targetsOnly:aBoolean
    showOnly := DefaultShowOnly := nil.
    aBoolean ifTrue:[
        showOnly := DefaultShowOnly := #targets
    ].

    "Modified: / 05-05-2011 / 15:24:02 / cg"
!

typesOnly
    ^ showOnly == #types

    "Modified: / 07-06-2010 / 14:19:06 / cg"
!

typesOnly:aBoolean
    showOnly := DefaultShowOnly := nil.
    aBoolean ifTrue:[
        showOnly := "DefaultShowOnly :=" #types
    ].

    "Modified: / 05-05-2011 / 15:24:04 / cg"
!

variablesOnly
    ^ showOnly == #variables

    "Modified: / 07-06-2010 / 14:19:09 / cg"
!

variablesOnly:aBoolean
    showOnly := nil.
    aBoolean ifTrue:[
        showOnly := DefaultShowOnly := #variables
    ].

    "Modified: / 05-05-2011 / 15:24:06 / cg"
! !

!TagList methodsFor:'accessing-presentation'!

groupBy
    ^ groupBy

    "Created: / 05-05-2011 / 14:31:37 / cg"
    "Modified: / 05-05-2011 / 15:34:14 / cg"
!

groupBy:aSymbolOrNil
    groupBy ~~ aSymbolOrNil ifTrue:[
        groupBy := DefaultGroupBy := aSymbolOrNil.
        self updateContentsFromFilteredList
    ].

    "Created: / 05-05-2011 / 14:32:00 / cg"
!

groupedByType
    ^ self groupBy == #byType

    "Created: / 05-05-2011 / 14:32:53 / cg"
!

groupedByType:aBoolean
    aBoolean == true ifTrue:[
        self groupBy:#byType
    ] ifFalse:[
        self groupBy:nil
    ].

    "Created: / 05-05-2011 / 14:33:05 / cg"
!

sortCriteria
    ^ sortCriteria ? DefaultSortCriteria
!

sortCriteria:aSymbolOrNil
    sortCriteria ~~ aSymbolOrNil ifTrue:[
        sortCriteria := DefaultSortCriteria := aSymbolOrNil.
        Sorted := sortCriteria.
        self updateContentsFromFilteredList
    ].

    "Modified: / 05-05-2011 / 14:50:18 / cg"
!

sorted
    "backward compatibility"

    ^ self sortCriteria notNil 
!

sorted:aBoolean
    "backward compatibility"

    aBoolean ifTrue:[
        self sortCriteria:#byName
    ] ifFalse:[
        self sortCriteria:nil
    ].
!

sortedByLineNumber
    ^ self sortCriteria isNil
    or:[ self sortCriteria == #lineNumber ]

    "Modified: / 05-05-2011 / 14:30:33 / cg"
!

sortedByLineNumber:aBoolean
    aBoolean == true ifTrue:[
        self sortCriteria:#lineNumber
    ].

    "Modified: / 27-06-2010 / 21:31:44 / cg"
!

sortedByName
    ^ self sortCriteria == #byName 
!

sortedByName:aBoolean
    aBoolean == true ifTrue:[
        self sortCriteria:#byName
    ].
!

sortedByNameIgnoringCase
    ^ self sortCriteria == #byNameIgnoringCase 
!

sortedByNameIgnoringCase:aBoolean
    aBoolean == true ifTrue:[
        self sortCriteria:#byNameIgnoringCase
    ].
!

sortedByNameIgnoringLeadingUnderscores
    ^ self sortCriteria == #byNameIgnoringLeadingUnderscores 
!

sortedByNameIgnoringLeadingUnderscores:aBoolean
    aBoolean == true ifTrue:[
        self sortCriteria:#byNameIgnoringLeadingUnderscores
    ].
!

sortedByNameIgnoringLeadingUnderscoresAndCase
    ^ self sortCriteria == #byNameIgnoringLeadingUnderscoresAndCase 
!

sortedByNameIgnoringLeadingUnderscoresAndCase:aBoolean
    aBoolean == true ifTrue:[
        self sortCriteria:#byNameIgnoringLeadingUnderscoresAndCase
    ].
!

sortedByType
    ^ self sortCriteria == #byType 
!

sortedByType:aBoolean
    aBoolean == true ifTrue:[
        self sortCriteria:#byType
    ].
!

tagTypesPresent
    ^ tagTypesPresent
! !

!TagList methodsFor:'private'!

applyFilterToList:aList
    ^ aList
        select:[:tag |
            tag label includesString:filter caseSensitive:false
        ]
!

getCtagsVersion
    " parse major and minor version from ctags by operating system command
      cehck for the 'Exuberant Ctags' string being present
      return an Array with mafor and minor part of version or nil if not available"

    | stream string index majorVersion minorVersion indexOfPoint|

    stream := WriteStream on:''.
    OperatingSystem         
        executeCommand:'ctags --version' 
        inputFrom:nil 
        outputTo:stream 
        errorTo:stream 
        inDirectory:nil
        onError:[:status| false].
    string := stream contents.
    index := string findString:'Exuberant Ctags' ifAbsent:[nil].
    index notNil ifTrue:[
        string := (string copyFrom:(index + ('Exuberant Ctags' size))) asArrayOfSubstrings first.
        (string includes:$,) ifTrue:[ string := string copyTo:((string indexOf:$,) - 1)].
        indexOfPoint := string indexOf:$. ifAbsent:nil.
        indexOfPoint notNil ifTrue:[
            majorVersion := (string copyFrom:1 to:indexOfPoint - 1) asInteger.
            minorVersion := (string copyFrom:indexOfPoint + 1 to:string size) asInteger.
            ^ Array with:majorVersion with:minorVersion.
        ]
    ].
    ^ nil

    "Modified: / 05-05-2011 / 14:48:08 / cg"
!

setFilteredList:aList
    filteredList := aList.
    self updateContentsFromFilteredList

    "Created: / 05-05-2011 / 14:46:12 / cg"
!

setRawList:aList
    rawList := aList.
    self updateContentsFromRawList

    "Created: / 05-05-2011 / 14:46:22 / cg"
!

shellCommandFor:aFilenameString
    "returns the shellCommand to be used"

    |lcSuffix shellCommand isCSuffix isCPlusPlusSuffix isJavaSuffix isEiffelSuffix isFortranSuffix
     showOnly response suff fn|

    ctagsCommand isNil ifTrue:[
        target isNil ifTrue:[
            "/ local use
            suff := (OperatingSystem isMSWINDOWSlike) ifTrue:'.exe' ifFalse:''.

            ctagsCommand := Smalltalk getPackageFileName:'stx/support/tools/ctags-5.0.1/ctags',suff.
            (ctagsCommand notNil and:[(fn := ctagsCommand asFilename) isExecutableProgram]) ifTrue:[
                ctagsCommand := fn pathName.
                ctagsIsExCtags := ctagsIsExCtags5x := true.
            ] ifFalse:[
                ctagsCommand := Smalltalk getPackageFileName:'stx/support/tools/ctags-3.2.2/ctags',suff.
                (ctagsCommand notNil and:[(fn := ctagsCommand asFilename) isExecutableProgram]) ifTrue:[
                    ctagsCommand := fn pathName.
                    ctagsIsExCtags := true.
                    ctagsIsExCtags5x := false.
                ] ifFalse:[
                    ctagsIsExCtags := nil.
                    ctagsIsExCtags5x := nil.
                    ctagsCommand := Smalltalk getPackageFileName:'stx/support/tools/ctags/ctags',suff.
                    (ctagsCommand notNil and:[(fn := ctagsCommand asFilename) isExecutableProgram]) ifTrue:[
                        ctagsCommand := fn pathName.
                    ] ifFalse:[
                        "/ use systems default ctags command
                        ctagsCommand := 'ctags'.
                    ]
                ]
            ].
        ] ifFalse:[
            "/ cross-development
"/            target remoteOperatingSystem = 'Linux' ifTrue:[
                "/ use systems default ctags command
                ctagsCommand := 'ctags'.
                ctagsIsExCtags := nil.
                ctagsIsExCtags5x := nil.
"/            ]
        ].
    ].

    (ctagsIsExCtags isNil or:[ctagsIsExCtags5x isNil]) ifTrue:[
        ctagsCommand notNil ifTrue:[
            response := OperatingSystem getCommandOutputFrom:(ctagsCommand, ' --version').
            (response notNil 
            and:[response asLowercase startsWith:'exuberant ctags']) ifTrue:[
                ctagsIsExCtags := true.

                response := (response copyFrom:'exuberant ctags' size + 1) withoutSeparators.
                ctagsIsExCtags5x := response startsWith:'5.' 
            ].
        ].
    ].

    shellCommand := ctagsCommand.
    (shellCommand includes:Character space) ifTrue:[
        shellCommand := '"',shellCommand,'"'.
    ].

    showOnly := self showOnly.

    lcSuffix := aFilenameString asFilename suffix asLowercase.

    isCSuffix := self class isCSuffix:lcSuffix.
    isCPlusPlusSuffix := self class isCPlusPlusSuffix:lcSuffix.

    (shellCommand notNil and:[(ctagsIsExCtags ? false)]) ifTrue:[
        isJavaSuffix := self class isJavaSuffix:lcSuffix.
        isEiffelSuffix := self class isEiffelSuffix:lcSuffix.
        isFortranSuffix := self class isFortranSuffix:lcSuffix.

        "/ ex_ctags supports c, c++, java, fortran and a few others
        (isCSuffix or:[isCPlusPlusSuffix or:[isJavaSuffix or:[isEiffelSuffix or:[isFortranSuffix]]]]) ifFalse:[
            (ctagsIsExCtags5x ? false) ifFalse:[
                ^ nil
            ].
            "/ ex_ctags5.x also supports awk, lisp, perl, pascal and a few others
"/            ^ nil
        ].

        usingDefaultCTags    := false.
        shellCommand := shellCommand asFilename asAbsoluteFilename pathName.
"/            shellCommand := shellCommand, ' -f - --c-types=f  --file-scope=no'.
"/            shellCommand := shellCommand, ' -f - --file-scope=yes'.
"/            shellCommand := shellCommand, ' -f - --file-scope=yes'.
        shellCommand := shellCommand, ' -f - --file-scope=yes --excmd=number'.

        (isCSuffix or:[isCPlusPlusSuffix]) ifTrue:[
            isCPlusPlusSuffix 
                ifTrue:[ shellCommand := shellCommand, ' --lang=c++']
                ifFalse:[ shellCommand := shellCommand, ' --lang=c'].

            showOnly == #classes ifTrue:[
                shellCommand := shellCommand, ' --c-types=c'
            ] ifFalse:[
                showOnly == #functions ifTrue:[
                    shellCommand := shellCommand, ' --c-types=f'
                ] ifFalse:[
                    showOnly == #functionsAndVariables ifTrue:[
                        shellCommand := shellCommand, ' --c-types=fv'
                    ] ifFalse:[
                        showOnly == #classesFunctionsAndVariables ifTrue:[
                            shellCommand := shellCommand, ' --c-types=cfv'
                        ] ifFalse:[
                            showOnly == #variables ifTrue:[
                                shellCommand := shellCommand, ' --c-types=v'
                            ] ifFalse:[
                                showOnly == #types ifTrue:[
                                    shellCommand := shellCommand, ' --c-types=t'
                                ] 
                            ] 
                        ] 
                    ] 
                ] 
            ]. 
            hideStructMembers == true ifTrue:[
                shellCommand := shellCommand, ' --c-types=-m'
            ].
            hideDefines == true ifTrue:[                
                shellCommand := shellCommand, ' --c-types=-d'
            ].
            hideTypedefs == true ifTrue:[
                shellCommand := shellCommand, ' --c-types=-t'
            ].
            hideStructures == true ifTrue:[
                shellCommand := shellCommand, ' --c-types=-s'
            ].
            hideVariables == true ifTrue:[
                shellCommand := shellCommand, ' --c-types=-v'
            ].
            hideFunctions == true ifTrue:[
                shellCommand := shellCommand, ' --c-types=-f'
            ].
            hideClasses == true ifTrue:[
                shellCommand := shellCommand, ' --c-types=-c'
            ].
        ].
        isJavaSuffix ifTrue:[
            shellCommand := shellCommand, ' --lang=java'.

            showOnly == #javaClasses ifTrue:[
                shellCommand := shellCommand, ' --java-types=c'
            ] ifFalse:[
                showOnly == #javaMethods ifTrue:[
                    shellCommand := shellCommand, ' --java-types=m'
                ] ifFalse:[
                    showOnly == #javaClassesAndMethods ifTrue:[
                        shellCommand := shellCommand, ' --java-types=mc'
                    ]
                ]
            ]. 
            hideJavaClasses == true ifTrue:[
                shellCommand := shellCommand, ' --java-types=-c'
            ].
            hideJavaMethods == true ifTrue:[
                shellCommand := shellCommand, ' --java-types=-m'
            ].
            hideJavaInterfaces == true ifTrue:[
                shellCommand := shellCommand, ' --java-types=-i'
            ].
            hideJavaFields == true ifTrue:[
                shellCommand := shellCommand, ' --java-types=-f'
            ].
            hideJavaPackages == true ifTrue:[
                shellCommand := shellCommand, ' --java-types=-p'
            ].
        ].
        isEiffelSuffix ifTrue:[
            shellCommand := shellCommand, ' --lang=eiffel'.

            showOnly == #classes ifTrue:[
                shellCommand := shellCommand, ' --eiffel-types=c'
            ] ifFalse:[
                showOnly == #features ifTrue:[
                    shellCommand := shellCommand, ' --eiffel-types=f'
                ]
            ]. 
"/            hideEiffelClasses == true ifTrue:[
"/                shellCommand := shellCommand, ' --eiffel-types=-c'
"/            ].
"/            hideEiffelFeatures == true ifTrue:[
"/                shellCommand := shellCommand, ' --eiffel-types=-m'
"/            ].
        ].

        isFortranSuffix ifTrue:[
            shellCommand := shellCommand, ' --lang=fortran'.

            showOnly == #functions ifTrue:[
                shellCommand := shellCommand, ' --fortran-types=f'
            ] ifFalse:[
                showOnly == #interfaces ifTrue:[
                    shellCommand := shellCommand, ' --fortran-types=i'
                ] ifFalse:[
                    showOnly == #subroutines ifTrue:[
                        shellCommand := shellCommand, ' --fortran-types=s'
                    ] ifFalse:[
                        showOnly == #commonBlocks == true ifTrue:[
                            shellCommand := shellCommand, ' --fortran-types=c'
                        ]
                    ]
                ]
            ]. 
"/            hideFortranFunctions == true ifTrue:[
"/                shellCommand := shellCommand, ' --fortran-types=-f'
"/            ].
"/            hideFortranInterfaces == true ifTrue:[
"/                shellCommand := shellCommand, ' --fortran-types=-i'
"/            ].
"/            hideFortranSubroutines == true ifTrue:[
"/                shellCommand := shellCommand, ' --fortran-types=-s'
"/            ].
"/            hideFortranCommonBlocks == true ifTrue:[
"/                shellCommand := shellCommand, ' --fortran-types=-c'
"/            ].
"/            hideFortranEntryPoints == true ifTrue:[
"/                shellCommand := shellCommand, ' --fortran-types=-e'
"/            ].
"/            hideFortranLabels == true ifTrue:[
"/                shellCommand := shellCommand, ' --fortran-types=-l'
"/            ].
"/            hideFortranDerivedTypes == true ifTrue:[
"/                shellCommand := shellCommand, ' --fortran-types=-t'
"/            ].
        ].

"/            shellCommand := shellCommand, ' -f -'.
        shellCommand := shellCommand, ' "' , aFilenameString, '"'.
        target notNil ifTrue:[
            ^ (target makeRemoteCommandFrom:shellCommand inDirectory:'./').
        ].
        ^ shellCommand.
    ].

    "/ regular ctags: assume supports c, c++ only
    isCSuffix ifFalse:[
        ^ nil
    ].

    usingDefaultCTags    := true.

    shellCommand := 'ctags'.

"/   "sunos and realIX have no option -s"
"/    (OperatingSystem getOSType  = 'linux') ifTrue:[
"/        shellCommand := 'ctags -S'
"/    ].
    Transcript showCR:('using default ctags command (not ctags from stx): <', shellCommand, '>').
    ctagsCommand := nil. "/ flush - so we will check again.

    shellCommand := shellCommand, ' ' , aFilenameString.
    target notNil ifTrue:[
        ^ (target makeRemoteCommandFrom:shellCommand inDirectory:'./').
    ].
    ^ shellCommand

    "Modified: / 08-07-2010 / 00:23:24 / cg"
!

sortBlock
    "sort AND group"

    |sortBlock|

    sortCriteria := self sortCriteria.
    sortBlock := self sortBlockForSortCriteria.

    groupBy isNil ifTrue:[
        ^ sortBlock
    ].

    ^ [:a :b| 
            |t1 t2 l1 l2|

            t1 := a typeIdentifierInList ? ' '.
            t2 := b typeIdentifierInList ? ' '.
            t1 = t2 ifTrue:[
                sortBlock value:a value:b
            ] ifFalse:[
                t1 < t2 
            ]
      ].

    "Modified: / 05-05-2011 / 15:35:02 / cg"
!

sortBlockForSortCriteria
    sortCriteria == #byName ifTrue:[ 
        ^ [:a :b| 
                |l1 l2|

                l1 := a label.
                l2 := b label.
                l1 = l2 ifTrue:[
                    (a lineNumber ? 0) < (b lineNumber ? 0)
                ] ifFalse:[
                    l1 < l2 
                ]
            ]
    ].

    sortCriteria == #byNameIgnoringCase ifTrue:[ 
        ^ [:a :b| 
                |l1 l2|

                l1 := a label asLowercase.
                l2 := b label asLowercase.
                l1 = l2 ifTrue:[
                    (a lineNumber ? 0) < (b lineNumber ? 0)
                ] ifFalse:[
                    l1 < l2 
                ]
          ]
    ].

    sortCriteria == #byNameIgnoringLeadingUnderscores ifTrue:[
        ^ [:a :b| 
                |l1 l2 i|

                l1 := a label.
                l2 := b label.
                l1 = l2 ifTrue:[
                    (a lineNumber ? 0) < (b lineNumber ? 0)
                ] ifFalse:[
                    i := l1 findFirst:[:c | (c ~~ $_)].
                    i > 1 ifTrue:[
                        l1 := l1 copyFrom:i
                    ].
                    i := l2 findFirst:[:c | (c ~~ $_)].
                    i > 1 ifTrue:[
                        l2 := l2 copyFrom:i
                    ].
                    l1 < l2 
                ]
          ].
    ].

    sortCriteria == #byNameIgnoringLeadingUnderscoresAndCase ifTrue:[
        ^ [:a :b| 
                |l1 l2 i|

                l1 := a label asLowercase.
                l2 := b label asLowercase.
                l1 = l2 ifTrue:[
                    (a lineNumber ? 0) < (b lineNumber ? 0)
                ] ifFalse:[
                    i := l1 findFirst:[:c | (c ~~ $_)].
                    i > 1 ifTrue:[
                        l1 := l1 copyFrom:i
                    ].
                    i := l2 findFirst:[:c | (c ~~ $_)].
                    i > 1 ifTrue:[
                        l2 := l2 copyFrom:i
                    ].
                    l1 < l2 
                ]
          ].
    ].

"/    sortCriteria == #byType ifTrue:[ 
"/        ^ [:a :b| 
"/                |t1 t2 l1 l2|
"/                t1 := a typeIdentifierInList ? ' '.
"/                t2 := b typeIdentifierInList ? ' '.
"/                t1 = t2 ifTrue:[
"/                    l1 := a label.
"/                    l2 := b label.
"/                    l1 = l2 ifTrue:[
"/                        (a lineNumber ? 0) < (b lineNumber ? 0)
"/                    ] ifFalse:[
"/                        l1 < l2 
"/                    ]
"/                ] ifFalse:[
"/                    t1 < t2 
"/                ]
"/          ].
"/    ].

    ^ [:a :b| a lineNumber < b lineNumber ]

    "Created: / 05-05-2011 / 14:37:25 / cg"
!

updateContentsFromFilteredList
    "call this, if only the sort order has changed (no need to call ctags or filter again)"

    |list|

    list := filteredList.
    list notEmptyOrNil ifTrue:[
        list := list asSortedCollection:(self sortBlock).
    ].
    self contents:(list ? #()).

    "Created: / 05-05-2011 / 14:45:41 / cg"
!

updateContentsFromRawList
    "call this, if only the filter has changed (no need to call ctags again)"

    filteredList := (filter isEmptyOrNil or:[rawList isNil])
                        ifTrue:[ rawList ]
                        ifFalse:[ self applyFilterToList:rawList ].

    self updateContentsFromFilteredList

    "Modified: / 05-05-2011 / 15:13:14 / cg"
! !

!TagList methodsFor:'queries'!

bestTagForLine:lineNr 
    |bestTag sortedByLineNumber|

    sortedByLineNumber := self sortedByLineNumber.
    self do:[:eachTag |
        eachTag notNil ifTrue:[
            eachTag lineNumber <= lineNr ifTrue:[
                bestTag isNil ifTrue:[
                    bestTag := eachTag.
                    "/ sortedByLineNumber ifTrue:[^ eachTag].
                ] ifFalse:[
                    eachTag lineNumber > bestTag lineNumber ifTrue:[
                        bestTag := eachTag    
                    ]
                ]
            ].
        ].
    ].

    ^ bestTag
! !

!TagList methodsFor:'tag generation'!

fromFile:aFile in:aTempDirectory
    "create tags from a file;
     either use the ctags/etags command, or an intenral naive, simple method."

    |list shellCmd numTags fileContents|

    rawList := nil.
    list := OrderedCollection new.

    shellCmd := (self shellCommandFor:aFile pathName).
    shellCmd isNil ifTrue:[
        list := self getSimpleTagListFromFile:aFile.
    ] ifFalse:[
        tagTypesPresent := false.     "/ will be set again, when ctags command provides types
        list := self getTagListFromFile:aFile usingCommand:shellCmd in:aTempDirectory
    ].
    tagTypesPresent := true.

    numTags := list size.
    fileContents := aFile contents.

    (numTags > 1 and:[fileContents notEmptyOrNil]) ifTrue:[
        numTags to:1 by:-1 do:[:i| 
            |tag lnr|

            tag := list at:i ifAbsent:nil.

            lnr := tag lineNumberIn:fileContents.
            lnr == 0 ifTrue:[
                list removeIndex:i
            ] ifFalse:[
                tag lineNumber:lnr
            ]
        ]
    ].    
    self setRawList:list.

    "Modified: / 05-05-2011 / 14:47:08 / cg"
!

fromFile:aFile in:aTempDirectory onTarget:aTarget
    "create tags from a file;
     either use the ctags/etags command, or an intenral naive, simple method.
    "
    |list|

    target := aTarget.

    [ 
        list := self fromFile:aFile in:aTempDirectory
    ] valueNowOrOnUnwindDo:[
        target := nil.
    ].
    ^ list
!

getModeFromFileSuffixOf:aFile 
    |suffix mode|

    suffix := aFile suffix.
    (self class isCSuffix:suffix) ifTrue:[
        ^ #c.
    ].
    (self class isCPlusPlusSuffix:suffix) ifTrue:[
        ^ #c.
    ].
    (self class isJavaSuffix:suffix) ifTrue:[
        ^ #java.
    ].
    (self class isFortranSuffix:suffix) ifTrue:[
        ^ #fortran.
    ].
    (self class isEiffelSuffix:suffix) ifTrue:[
        ^ #eiffel.
    ].
    (self class isHTMLSuffix:suffix) ifTrue:[
        ^ #html.
    ].
    ^ mode

    "Modified: / 20-04-2011 / 19:02:54 / cg"
!

getTagListFromFile:aFile usingCommand:scmd in:aTempDirectory
    "create ctags-list from a file, using cmd (which is etags / ctags)"

    |list pipe tag tagFile contents mode infoDictionary|

    mode := self getModeFromFileSuffixOf:aFile.

    list := OrderedCollection new:512.

    infoDictionary := Dictionary new.

"/    Transcript showCR:'execute tags command: ', scmd.
    usingDefaultCTags ifFalse:[
        (pipe := PipeStream readingFrom:scmd) notNil ifTrue:[
            [
                |line atEnd|

                atEnd := false.
                ReadError 
                    handle:[:ex | ]
                    do:[
                        [atEnd] whileFalse:[
                            (line := pipe nextLine) isNil ifTrue:[
                                atEnd := pipe atEnd
                            ] ifFalse:[
"/ Transcript showCR:line.
                                tag := self tagFromLine:line mode:mode using:infoDictionary.

                                tag notNil ifTrue:[
                                    list add:tag
                                ]
                            ]
                        ]
                    ]
            ] ensure:[pipe close].
        ].
        ^ list.
    ].

    (OperatingSystem executeCommand:scmd inDirectory:aTempDirectory) ifTrue:[
        tagFile := aTempDirectory construct:'tags'.

        tagFile exists ifTrue:[
            contents := tagFile contents.

            contents notNil ifTrue:[
                contents do:[:aLine|
                    (tag := self tagFromLine:aLine mode:mode using:infoDictionary) notNil ifTrue:[list add:tag]
                ]
            ].
            Exception 
                handle:[:ex| ] 
                do:[tagFile remove].
        ].
        ^ list.
    ].

    scmd = 'ctags' ifFalse:[
        "/ try default ctags without any options
        ^ self getTagListFromFile:aFile usingCommand:'ctags' in:aTempDirectory
    ].
    ^ #()
!

tagFromLine:aLine mode:languageMode using:infoDictionary
    "analyze the line as returned from ctags and create a corresponding tag object for it"

    |stream word1 word2 tagType pattern key 
     file className lineNumber tagClass fmtString fmt
     showOnly|

"/ Transcript showCR:aLine.
    aLine size < 6 ifTrue:[
        ^ nil
    ].
    aLine first == $!! ifTrue:[
        (aLine startsWith:'!!_TAG_FILE_FORMAT') ifTrue:[
            "/ aha - ex. ctags
            stream := aLine readStream.
            stream upTo:Character tab.
            stream skipSeparators.
            fmtString := stream upTo:Character tab.
            fmt := Integer readFrom:fmtString onError:nil.
            fmt notNil ifTrue:[
                infoDictionary at:#formatVersion put:fmt
            ]
        ].
        ^ nil
    ].

    "/ tab separated list; except for the pattern, which might include a tab.
    stream := aLine readStream.
    key := stream upTo:Character tab.
    stream skipSeparators.
    file := stream upTo:Character tab.
    stream skipSeparators.
    stream peek == $/ ifTrue:[
        stream next.
        pattern := stream upTo:$/.
        [(pattern last) == $\] whileTrue:[
            pattern at:(pattern size) put:$/.
            pattern := pattern , (stream upTo:$/).
        ].
    ] ifFalse:[
        stream peek isDigit ifTrue:[
            lineNumber := Integer readFrom:stream onError:nil.
            lineNumber isNil ifTrue:[
                self halt:'should not happen - please debug'.
            ] ifFalse:[
                pattern := key.
            ].
        ] ifFalse:[
            self halt:'should not happen - please debug'.
        ].
    ].
    stream peekFor:$;.
    stream peekFor:$".
    stream skipSeparators.
    tagType := stream upTo:Character tab.
    stream skipSeparators.
    word1 := stream upTo:Character tab.     "/ optional file: (scope)
    stream skipSeparators.
    word2 := stream upTo:Character tab.     "/ optional class:

    (word1 startsWith:'file:') ifTrue:[     "/ file: (scope)
        hideStatic == true ifTrue:[^ nil].
    ].

    (word2 startsWith: 'class:') ifTrue:[
        className := word2 copyFrom:('class:' size)
    ] ifFalse:[
        (word1 startsWith: 'class:') ifTrue:[
            className := word1 copyFrom:('class:' size)
        ]
    ].
"/    (word1 startsWith: 'class:') ifTrue:[
"/        className := word1 copyFrom:('class:' size)
"/    ].
"/    (word2 startsWith: 'class:') ifTrue:[
"/        className := word2 copyFrom:('class:' size)
"/    ].

    tagClass := Tag.
    tagClass autoload.

    "/ typeCharacter to tag-Class mapping...
    languageMode == #c ifTrue:[
        tagType = 'v' ifTrue:[ 
            hideVariables == true ifTrue:[^ nil].
            tagClass := Tag::TVariable 
        ] ifFalse:[ tagType = 'f' ifTrue:[ 
            hideFunctions == true ifTrue:[^ nil].
            tagClass := Tag::TFunction 
        ] ifFalse:[ tagType = 'd' ifTrue:[ 
            hideDefines == true ifTrue:[^ nil].
            tagClass := Tag::TMacro 
        ] ifFalse:[ tagType = 't' ifTrue:[ 
            hideTypedefs == true ifTrue:[^ nil].
            tagClass := Tag::TTypedef 
        ] ifFalse:[ tagType = 'm' ifTrue:[ 
            hideStructMembers == true ifTrue:[^ nil].
            tagClass := Tag::TMember
        ] ifFalse:[ tagType = 's' ifTrue:[ 
            hideStructures == true ifTrue:[^ nil].
            tagClass := Tag::TStruct
        ] ifFalse:[ tagType = 'u' ifTrue:[ 
            hideStructures == true ifTrue:[^ nil].
            tagClass := Tag::TUnion
        ] ifFalse:[ tagType = 'c' ifTrue:[ 
            hideClasses == true ifTrue:[^ nil].
            tagClass := Tag::TClass
        ] ifFalse:[ tagType = 'e' ifTrue:[ 
            tagClass := Tag::TEnumMember. 
        ] ifFalse:[ tagType = 'g' ifTrue:[ 
            tagClass := Tag::TEnum. 
"/        ] ifFalse:[ tagType = 'n' ifTrue:[ 
"/            tagClass := Tag::TNamespace
"/        ] ifFalse:[ tagType = 'p' ifTrue:[ 
"/            tagClass := Tag::TFunctionPrototype
"/        ] ifFalse:[ tagType = 'x' ifTrue:[ 
"/            tagClass := Tag::TExternVariable
        ] ifFalse:[ 
            "/ add more here 
        ]]]]]]]]]]
    ] ifFalse:[ languageMode == #java ifTrue:[
        tagType = 'c' ifTrue:[ 
            hideJavaClasses == true ifTrue:[^ nil].
            tagClass := Tag::TClass 
        ] ifFalse:[ tagType = 'm' ifTrue:[ 
            hideJavaMethods == true ifTrue:[^ nil].
            tagClass := Tag::TMethod
        ] ifFalse:[ tagType = 'f' ifTrue:[ 
            hideJavaFields == true ifTrue:[^ nil].
            tagClass := Tag::TField
        ] ifFalse:[ tagType = 'i' ifTrue:[ 
            hideJavaInterfaces == true ifTrue:[^ nil].
            tagClass := Tag::TInterface
        ] ifFalse:[ tagType = 'p' ifTrue:[ 
            hideJavaPackages == true ifTrue:[^ nil].
            tagClass := Tag::TPackage
        ] ifFalse:[
            "/ add more here */
        ]]]]]
    ] ifFalse:[ languageMode == #eiffel ifTrue:[
        tagType = 'c' ifTrue:[ 
            hideClasses == true ifTrue:[^ nil].
            tagClass := Tag::TClass 
"/        ] ifFalse:[ tagType = 'f' ifTrue:[ 
"/            tagClass := Tag::TFeature
"/        ] ifFalse:[ tagType = 'l' ifTrue:[ 
"/            tagClass := Tag::TLocalEntity
        ] ifFalse:[
            "/ add more here */
        ]
    ] ifFalse:[ languageMode == #fortran ifTrue:[
        tagType = 'f' ifTrue:[ 
            hideFunctions == true ifTrue:[^ nil].
            tagClass := Tag::TFunction 
        ] ifFalse:[ tagType = 'i' ifTrue:[ 
"/            hideInterfaces == true ifTrue:[^ nil].
            tagClass := Tag::TInterface
        ] ifFalse:[ tagType = 't' ifTrue:[ 
            hideTypedefs == true ifTrue:[^ nil].
            tagClass := Tag::TTypedef 
"/        ] ifFalse:[ tagType = 'l' ifTrue:[ 
"/            tagClass := Tag::TLabel
"/        ] ifFalse:[ tagType = 'm' ifTrue:[ 
"/            tagClass := Tag::TModule
"/        ] ifFalse:[ tagType = 'n' ifTrue:[ 
"/            tagClass := Tag::TNameList
"/        ] ifFalse:[ tagType = 'p' ifTrue:[ 
"/            tagClass := Tag::TProgram
"/        ] ifFalse:[ tagType = 's' ifTrue:[ 
"/            tagClass := Tag::TSubroutine
"/        ] ifFalse:[ tagType = 'b' ifTrue:[ 
"/            tagClass := Tag::TBlockData
"/        ] ifFalse:[ tagType = 'c' ifTrue:[ 
"/            tagClass := Tag::TCommonBlock
"/        ] ifFalse:[ tagType = 'e' ifTrue:[ 
"/            tagClass := Tag::TEntryPoint
        ] ifFalse:[
            "/ add more here */
        ]]]
    ]]]].

    tagTypesPresent := true.

    tagType size == 0 ifTrue:[
        tagType := ''
    ] ifFalse:[
        (showOnly := self showOnly) notNil ifTrue:[
            showOnly == #classes ifTrue:[
                tagClass ~~ Tag::TClass ifTrue:[^ nil].
            ] ifFalse:[ showOnly == #functions ifTrue:[
                tagClass ~~ Tag::TFunction ifTrue:[^ nil].
            ] ifFalse:[ showOnly == #variables ifTrue:[
                tagClass ~~ Tag::TVariable ifTrue:[^ nil].
            ] ifFalse:[ showOnly == #types ifTrue:[
                (tagClass ~~ Tag::TTypedef 
                and:[ true "tagClass ~~ Tag::TUnion" 
                and:[ tagClass ~~ Tag::TStruct ]])ifTrue:[^ nil].
            ] ifFalse:[ showOnly == #functionsAndVariables ifTrue:[
                ((tagClass ~~ Tag::TFunction) 
                and:[tagClass ~~ Tag::TVariable]) ifTrue:[^ nil].
            ] ifFalse:[ showOnly == #classesFunctionsAndVariables ifTrue:[
                ((tagClass ~~ Tag::TFunction) 
                and:[(tagClass ~~ Tag::TVariable)
                and:[tagClass ~~ Tag::TClass]]) ifTrue:[^ nil].
            ] ifFalse:[ showOnly == #defines ifTrue:[
                tagClass ~~ Tag::TMacro ifTrue:[^ nil].
            ] ifFalse:[ showOnly == #structs ifTrue:[
                tagClass ~~ Tag::TStruct ifTrue:[^ nil].
            ] ifFalse:[ showOnly == #everything ifTrue:[
            ] ifFalse:[
                self halt:'unhandled showOnly'.
            ]]]]]]]]]
        ]
    ].

    ^ tagClass label:key 
             pattern:pattern
                type:tagType
          lineNumber:lineNumber
           className:className.

    "Modified: / 05-05-2011 / 15:45:55 / cg"
! !

!TagList methodsFor:'tag generation - simple'!

assemblerTagsInFile:aFilePath
    "assembler tags:
     naive, q&d scan for lines matching:
        <anything>:
     CAVEAT:
        the code below handles linux-i386 assembler only (for now)
    "

    |targets line l lineNr nm s words w directive
     hideLocals hideData hideText currentSegment|

    Tag autoload.

    targets := OrderedCollection new.
    s := aFilePath asFilename readStream.
    s notNil ifTrue:[
        hideLocals := hideLocalLabels value ? false.
        hideData := hideDataLabels value ? false.
        hideText := hideTextLabels value ? false.
        currentSegment := #text.

        s := LineNumberReadStream readingFrom:s.
        [s atEnd] whileFalse:[
            lineNr := s lineNumber.
            line := s nextLine.
            l := line withoutSeparators.
            words := l asCollectionOfWords.
            words size >= 1 ifTrue:[
                w := words first.
                (w endsWith:$:) ifTrue:[
                    (hideText and:[currentSegment == #text]) ifFalse:[
                        (hideData and:[currentSegment == #data]) ifFalse:[
                            (hideLocals and:[(w startsWith:$.)]) ifFalse:[
                                nm := w copyWithoutLast:1.
                                targets add:(Tag::TLabel 
                                                label:nm 
                                                pattern:nil
                                                type:nil
                                                lineNumber:lineNr).
                            ].
                        ].
                    ].
                    words size >= 2 ifTrue:[
                        directive := words second
                    ] ifFalse:[
                        directive := nil.
                    ]
                ] ifFalse:[
                    directive := w.
                ].
                (directive notNil and:[directive startsWith:$.]) ifTrue:[
                     directive = '.text' ifTrue:[
                        currentSegment := #text
                    ] ifFalse:[ directive = '.data' ifTrue:[
                        currentSegment := #data
                    ] ifFalse:[ directive = '.bss' ifTrue:[
                        currentSegment := #data
                    ] ifFalse:[ directive = '.rodata' ifTrue:[
                        currentSegment := #data
                    ]]]]
                ]
            ]
        ].
        s close
    ].
    ^ targets





!

getSimpleTagListFromFile:aFile
    "fallback, if no ctags is present, or if the file is not a c-file.
     Implemented here for some other file types (Makefiles)
    "
    |lcName pathName suffix|

    lcName := aFile asFilename baseName asLowercase.
    pathName := aFile asFilename pathName.
    self class makeFilePatterns do:[:aPattern |
        (aPattern match:lcName) ifTrue:[
            ^ self class makeTargetTagsInFile:pathName filter:showOnly
        ]
    ].

    suffix := lcName asFilename suffix.

    (self class isSmalltalkSuffix:suffix) ifTrue:[
        "/ smalltalk tags - simulated
        ^ self stTagsInFile:pathName
    ].
    (self class isPythonSuffix:suffix) ifTrue:[
        "/ python tags - simulated
        ^ self pythonTagsInFile:pathName
    ].
    (self class isPhpSuffix:suffix) ifTrue:[
        "/ php tags - simulated
        ^ self phpTagsInFile:pathName
    ].
    (self class isLispSuffix:suffix) ifTrue:[
        "/ lisp tags - simulated
        ^ self lispTagsInFile:pathName
    ].
    (self class isOzSuffix:suffix) ifTrue:[
        "/ oz tags - simulated
        ^ self ozTagsInFile:pathName
    ].
    (self class isPrologSuffix:suffix) ifTrue:[
        "/ prolog tags - simulated
        ^ self prologTagsInFile:pathName
    ].
    (self class isTCLSuffix:suffix) ifTrue:[
        "/ tcl tags - simulated
        ^ self tclTagsInFile:pathName
    ].
    (self class isAssemblerSuffix:suffix) ifTrue:[
        "/ assembler tags - simulated
        ^ self assemblerTagsInFile:pathName
    ].
    (self class isRubySuffix:suffix) ifTrue:[
        "/ ruby tags - simulated
        ^ self rubyTagsInFile:pathName
    ].
    (self class isYaccSuffix:suffix) ifTrue:[
        "/ yacc tags - simulated
        ^ self yaccTagsInFile:pathName
    ].
    (self class isJavaScriptSuffix:suffix) ifTrue:[
        "/ js tags - simulated
        ^ self javaScriptTagsInFile:pathName
    ].

    (self class isHTMLSuffix:suffix) ifTrue:[
        "/ html tags - simulated
        ^ self htmlTagsInFile:pathName
    ].

    "/ could add more here ...
    ^ nil.

    "Modified: / 20-04-2011 / 19:06:26 / cg"
!

htmlTagsInFile:aFilePath
    "hatml tags:
     naive, q&d scan for lines containing with:
        <textarea>
        <input>
        <table>
        <script>
    "

    |targets line l lineNr s tag|

    "/ TODO: use HTMPParser to read all of them !!

    Tag autoload.

    targets := OrderedCollection new.
    s := aFilePath asFilename readStream.
    s notNil ifTrue:[
        s := LineNumberReadStream readingFrom:s.
        [s atEnd] whileFalse:[
            lineNr := s lineNumber.
            line := s nextLine.
            l := line withoutSeparators asLowercase.

            #(
                'textarea'      hideHTMLTextArea
                'input'         hideHTMLInput
                'table'         hideHTMLTable
                'script'        hideHTMLScript  
            ) pairWiseDo:[:nm :hideInstVarName|
                |type hideHolder idx tagText doc markup label|

                type := hideHolder := nil.

                idx := l indexOfSubCollection:('<',nm).
                idx ~~ 0 ifTrue:[
                    type := Tag::TElement.
                    hideHolder := self instVarNamed:hideInstVarName.

                    tagText := l copyFrom:idx.
                    doc := HTMLParser new parseText:tagText.
                    markup := doc markup.
                    markup id notEmptyOrNil ifTrue:[
                        label := nm , ' (',markup id,')'
                    ] ifFalse:[
                        markup name notEmptyOrNil ifTrue:[
                            label := nm , ' (',markup name,')'
                        ] ifFalse:[
                            label := nm
                        ].
                    ].


                    hideHolder value ~~ true ifTrue:[
                        tag := type 
                                    label:label 
                                    pattern:nil
                                    type:nil
                                    lineNumber:lineNr.
                        targets add:tag.
                    ]
                ].
            ].
        ].
        s close
    ].
    ^ targets

    "Created: / 20-04-2011 / 18:59:29 / cg"
!

javaScriptTagsInFile:aFilePath
    "javaScript tags:
     naive, q&d scan for lines matching:
        (function foo
    "

    |targets line l lineNr nm s|

    Tag autoload.

    targets := OrderedCollection new.
    s := aFilePath asFilename readStream.
    s notNil ifTrue:[
        s := LineNumberReadStream readingFrom:s.
        [s atEnd] whileFalse:[
            lineNr := s lineNumber.
            line := s nextLine.
            l := line withoutSeparators.

            (l startsWith:'function ') ifTrue:[
                (showOnly isNil or:[showOnly == #functions]) ifTrue:[
                    hideFunctions value ~~ true ifTrue:[
                        nm := l copyFrom:('function ' size + 1).
                        nm := nm copyTo:(nm 
                                            findFirst:[:ch | (ch isLetterOrDigit or:['$_' includes:ch]) not] 
                                            ifNone:nm size+1)-1.
                        targets add:(Tag::TFunction 
                                        label:nm 
                                        pattern:nil
                                        type:nil
                                        lineNumber:lineNr).
                    ]
                ]
            ] ifFalse:[
                (l startsWith:'var ') ifTrue:[
                    (showOnly isNil or:[showOnly == #variables]) ifTrue:[
                        hideVariables value ~~ true ifTrue:[
                            nm := l copyFrom:('var ' size + 1).
                            nm := nm copyTo:(nm 
                                                findFirst:[:ch | (ch isLetterOrDigit or:['$_' includes:ch]) not] 
                                                ifNone:nm size+1)-1.
                            targets add:(Tag::TVariable 
                                            label:nm 
                                            pattern:nil
                                            type:nil
                                            lineNumber:lineNr).
                        ].
                    ].
                ].
            ]
        ].
        s close
    ].
    ^ targets

    "Created: / 28-06-2010 / 12:44:25 / cg"
!

lispTagFromLine:line lineNr:lineNr
    "lisp tags:
     naive, q&d scan for lines starting with (not syntax-aware):
        (define ...
        (defun ...
        (defvar ...
        (defmacro ...
        (defclass ...
        (defmethod ...
        (defpackage ...
        (eval-when ...
        (define- ...
        (def* ...
        (set ...
        (constant ...
        (defconstant ...
    "

    |l nm words def arg inParens|

    l := line withoutSeparators.

    (l startsWith:'(') ifFalse:[^ nil].

    words := (l copyFrom:2) asCollectionOfWords.
    words size >= 2 ifFalse:[^ nil].

    def := words first.
    nm := words second.
    (inParens := nm startsWith:'(') ifTrue:[
        nm := nm copyFrom:2.
    ] ifFalse:[
        nm := nm upTo:$(.    "/ in case it is (define foo() - without space after name
        arg := l copyFrom:(l indexOf:$( startingAt:2 ifAbsent:2).   
        (inParens := nm startsWith:'(') ifTrue:[
            nm := nm copyFrom:2.
        ].
    ].
    (nm endsWith:')') ifTrue:[
        nm := nm copyWithoutLast:1
    ].

    def = 'defun' ifTrue:[
        (showOnly notNil and:[showOnly ~~ #functions]) ifTrue:[^ nil].
        hideFunctions value == true ifTrue:[ ^ nil ].
        ^ Tag::TFunction 
                        label:nm 
                        pattern:nil
                        type:nil
                        lineNumber:lineNr.
    ].
    def = 'define' ifTrue:[             "/ scheme
        inParens ifTrue:[
            (showOnly notNil and:[showOnly ~~ #functions]) ifTrue:[^ nil].
            hideFunctions value == true ifTrue:[ ^ nil ].
            ^ Tag::TFunction 
                            label:nm 
                            pattern:nil
                            type:nil
                            lineNumber:lineNr.
        ] ifFalse:[
            (showOnly notNil and:[showOnly ~~ #variables]) ifTrue:[^ nil].
            hideVariables value == true ifTrue:[ ^ nil ].
            ^ Tag::TVariable 
                            label:nm 
                            pattern:nil
                            type:nil
                            lineNumber:lineNr.
        ].
        ^ nil
    ].

    def = 'defvar' ifTrue:[
        (showOnly notNil and:[showOnly ~~ #variables]) ifTrue:[^ nil].
        hideVariables value == true ifTrue:[ ^ nil ].
        ^ Tag::TVariable 
                        label:nm 
                        pattern:nil
                        type:nil
                        lineNumber:lineNr.
    ].
    def = 'set' ifTrue:[
        hideVariables value == true ifTrue:[ ^ nil ].
        ^ Tag::TVariable 
                        label:nm 
                        pattern:nil
                        type:nil
                        lineNumber:lineNr.
    ].
    (def = 'defconstant' or:[def = 'constant']) ifTrue:[
        (showOnly notNil and:[showOnly ~~ #constants]) ifTrue:[^ nil].
        hideLispConstants value == true ifTrue:[ ^ nil ].
        ^ Tag::TLispConstant 
                        label:nm 
                        pattern:nil
                        type:nil
                        lineNumber:lineNr.
    ].
    (def = 'mac' or:[def = 'defmacro' or:[def = 'define-macro']]) ifTrue:[
        (showOnly notNil and:[showOnly ~~ #macros]) ifTrue:[^ nil].
        hideLispMacros value == true ifTrue:[ ^ nil ].
        ^ Tag::TLispMacro 
                        label:nm 
                        pattern:nil
                        type:nil
                        lineNumber:lineNr.
    ].
    (def = 'defclass' or:[def = 'define-class']) ifTrue:[
        (showOnly notNil and:[showOnly ~~ #classes]) ifTrue:[^ nil].
        hideClasses value == true ifTrue:[ ^ nil ].
        ^ Tag::TClass 
                        label:nm 
                        pattern:nil
                        type:nil
                        lineNumber:lineNr.
    ].
    (def = 'defmethod' or:[def = 'define-method' or:[def = 'define-generic']]) ifTrue:[
        (showOnly notNil and:[showOnly ~~ #methods]) ifTrue:[^ nil].
        hideLispMethods value == true ifTrue:[ ^ nil ].
        ^ Tag::TMethod 
                        label:nm 
                        pattern:nil
                        type:nil
                        lineNumber:lineNr.
    ].
    (def = 'defpackage') ifTrue:[
        hideLispMethods value == true ifTrue:[ ^ nil ].
        ^ Tag::TPackage 
                        label:nm 
                        pattern:nil
                        type:nil
                        lineNumber:lineNr.
    ].
    def = 'eval-when' ifTrue:[
        hideLispEvaluations value == true ifTrue:[ ^ nil ].
        ^ Tag::TLispEval 
                        label:arg 
                        pattern:nil
                        type:nil
                        lineNumber:lineNr.
    ].
    def = 'defstruct' ifTrue:[
        hideStructures value == true ifTrue:[ ^ nil ].
        ^ Tag::TStruct 
                        label:nm 
                        pattern:nil
                        type:nil
                        lineNumber:lineNr.
    ].
    (def startsWith:'def') ifTrue:[
        (showOnly notNil and:[showOnly ~~ #functions]) ifTrue:[^ nil].
        hideFunctions value == true ifTrue:[ ^ nil ].
        ^ Tag::TFunction 
                        label:nm 
                        pattern:nil
                        type:nil
                        lineNumber:lineNr.
    ].
    ^ nil

    "Modified: / 07-06-2010 / 11:17:18 / cg"
!

lispTagsInFile:aFilePath
    "lisp tags:
     naive, q&d scan for lines starting with (not syntax-aware):
        (define ...
        (defun ...
        (defvar ...
        (defmacro ...
        (defclass ...
        (defmethod ...
        (defpackage ...
        (eval-when ...
        (define- ...
        (def* ...
        (set ...
        (constant ...
        (defconstant ...
    "

    |targets line lineNr s tag|

    Tag autoload.

    targets := OrderedCollection new.
    s := aFilePath asFilename readStream.
    s notNil ifTrue:[
        s := LineNumberReadStream readingFrom:s.
        [s atEnd] whileFalse:[
            lineNr := s lineNumber.
            line := s nextLine.

            tag := self lispTagFromLine:line lineNr:lineNr.
            tag notNil ifTrue:[
                targets add:tag
            ].
        ].
        s close
    ].
    ^ targets

    "Modified: / 07-06-2010 / 11:02:51 / cg"
!

ozTagsInFile:aFilePath
    "oz tags:
     naive, q&d scan for lines starting with:
        fun { name ...
    "

    |targets line l lineNr nm s tag lineStream kwLen skipBrace type hideHolder|

    Tag autoload.

    targets := OrderedCollection new.
    s := aFilePath asFilename readStream.
    s notNil ifTrue:[
        s := LineNumberReadStream readingFrom:s.
        [s atEnd] whileFalse:[
            lineNr := s lineNumber.
            line := s nextLine.
            l := line withoutSeparators.

            kwLen := nil.
            skipBrace := false.

            (l startsWith:'class') ifTrue:[
                kwLen := 5.
                type := Tag::TClass.
                hideHolder := hideOzClasses.
            ].
            (l startsWith:'meth') ifTrue:[
                kwLen := 4.
                type := Tag::TMethod.
                hideHolder := hideOzMethods.
            ].
            (l startsWith:'fun') ifTrue:[
                kwLen := 3.
                skipBrace := true.
                type := Tag::TFunction.
                hideHolder := hideOzFunctions.
            ].
            (l startsWith:'proc') ifTrue:[
                kwLen := 4.
                skipBrace := true.
                type := Tag::TFunction.
                hideHolder := hideOzFunctions.
            ].
            hideHolder value ~~ true ifTrue:[
                kwLen notNil ifTrue:[
                    lineStream := l readStream.
                    lineStream skip:kwLen; skipSeparators.

                    (skipBrace not or:[lineStream peek = ${ ]) ifTrue:[
                        skipBrace ifTrue:[lineStream skip:1; skipSeparators].  
                        nm := lineStream upToMatching:[:ch | (ch isLetterOrDigit or:['_' includes:ch]) not].
                        (nm notEmpty and:[nm first isLetter or:[nm first = $_]]) ifTrue:[    
                            tag := type 
                                            label:nm 
                                            pattern:nil
                                            type:nil
                                            lineNumber:lineNr.
                            targets add:tag.
                        ]
                    ]
                ].
            ]
        ].
        s close
    ].
    ^ targets
!

phpTagsInFile:aFilePath
    "php tags:
     naive, q&d scan for lines starting with:
        var ...
        class ...
        function ...
    "

    |targets line l lineNr nm s lineStream|

    Tag autoload.

    targets := OrderedCollection new.
    s := aFilePath asFilename readStream.
    s notNil ifTrue:[
        s := LineNumberReadStream readingFrom:s.
        [s atEnd] whileFalse:[
            lineNr := s lineNumber.
            line := s nextLine.
            l := line withoutSeparators.

            (l startsWith:'var ') ifTrue:[
                lineStream := (l copyFrom:4) readStream.
                lineStream skipSeparators.
                lineStream peek == $$ ifTrue:[
                    lineStream next.
                    nm := lineStream 
                            nextMatching:[:c | c isLetter] 
                            thenMatching:[:c | c isLetterOrDigit or:[c == $_]].
                    targets add:(Tag::TVariable 
                                label:nm 
                                pattern:nil
                                type:nil
                                lineNumber:lineNr).
                ]
            ] ifFalse:[
                (l startsWith:'class ') ifTrue:[
                    lineStream := (l copyFrom:6) readStream.
                    lineStream skipSeparators.
                    nm := lineStream 
                            nextMatching:[:c | c isLetter] 
                            thenMatching:[:c | c isLetterOrDigit or:[c == $_]].
                    targets add:(Tag::TClass 
                                    label:nm 
                                    pattern:nil
                                    type:nil
                                    lineNumber:lineNr).
                ] ifFalse:[
                    (l startsWith:'function ') ifTrue:[
                        lineStream := (l copyFrom:9) readStream.
                        lineStream skipSeparators.
                        nm := lineStream 
                                nextMatching:[:c | c isLetter] 
                                thenMatching:[:c | c isLetterOrDigit or:[c == $_]].
                        targets add:(Tag::TFunction
                                        label:nm 
                                        pattern:nil
                                        type:nil
                                        lineNumber:lineNr).
                    ].
                ].
            ].
        ].
        s close
    ].
    ^ targets
!

prologTagsInFile:aFilePath
    "prolog tags:
     naive, q&d scan for lines matching:
        <anything> :-
    "

    |targets line l lineNr nm s|

    Tag autoload.

    targets := OrderedCollection new.
    s := aFilePath asFilename readStream.
    s notNil ifTrue:[
        s := LineNumberReadStream readingFrom:s.
        [s atEnd] whileFalse:[
            lineNr := s lineNumber.
            line := s nextLine.
            l := line withoutSeparators.

            (l includesString:':-') ifTrue:[
                (l startsWith:':-') ifFalse:[
                    nm := l copyTo:(l indexOfSubCollection:':-').
                    targets add:(Tag::TPrologClause 
                                    label:nm 
                                    pattern:nil
                                    type:nil
                                    lineNumber:lineNr).
                ]
            ]
        ].
        s close
    ].
    ^ targets





!

pythonTagsInFile:aFilePath
    "python tags:
     naive, q&d scan for lines matching
        class <anything> :
     or
        def <anything> :
    "

    |targets line l lineNr nm s inClass indent classIndent|

    Tag autoload.

    inClass := nil.
    targets := OrderedCollection new.
    s := aFilePath asFilename readStream.
    inClass := OrderedCollection new.
    classIndent := 0.

    s notNil ifTrue:[
        s := LineNumberReadStream readingFrom:s.
        [s atEnd] whileFalse:[
            lineNr := s lineNumber.
            line := s nextLine.
            l := line withoutSeparators.
            l size > 0 ifTrue:[

                line := line withTabsExpanded:8.
                indent := line findFirst:[:c | c ~~ Character space].
                indent := indent // 8.
                indent < classIndent ifTrue:[
                    inClass removeFirstIfAbsent:nil.
                    classIndent := classIndent - 1.
                ].

                (l startsWith:'class ') ifTrue:[
                    (l endsWith:':') ifTrue:[
                        nm := l copyFrom:7 to:(l size - 1).
                        nm := nm withoutSeparators.
                        (showOnly ~~ #pythonFunctions
                        and:[showOnly ~~ #pythonMethods]) ifTrue:[
                            hidePythonClasses value ~~ true ifTrue:[
                                targets add:(Tag::TClass 
                                                label:nm 
                                                pattern:nil
                                                type:nil
                                                lineNumber:lineNr).
                            ].
                        ].
                        nm := nm upTo:$(.
                        inClass addFirst:nm.
                        classIndent := indent + 1.
                    ]
                ] ifFalse:[
                    (l startsWith:'def ') ifTrue:[
                        (l endsWith:':') ifTrue:[
                            nm := l copyFrom:5 to:(l size - 1).
                            nm := nm withoutSeparators.

                            inClass size > 0 ifTrue:[
                                (showOnly ~~ #pythonFunctions
                                and:[showOnly ~~ #pythonClasses]) ifTrue:[
                                    hidePythonMethods value ~~ true ifTrue:[
                                        nm := inClass first , '.' , nm.
                                        targets add:(Tag::TMethod 
                                                        label:nm 
                                                        pattern:nil
                                                        type:nil
                                                        lineNumber:lineNr).
                                    ]
                                ]
                            ] ifFalse:[
                                (showOnly ~~ #pythonClasses
                                and:[showOnly ~~ #pythonMethods]) ifTrue:[
                                    hidePythonFunctions value ~~ true ifTrue:[
                                        targets add:(Tag::TFunction 
                                                        label:nm 
                                                        pattern:nil
                                                        type:nil
                                                        lineNumber:lineNr).
                                    ]
                                ]
                            ]
                        ]
                    ]
                ]
            ]
        ].
        s close
    ].
    ^ targets
!

rubyTagsInFile:aFilePath
    "ruby tags:
     naive, q&d scan for lines matching:
        def any
    "

    |targets line l lineNr nm s|

    Tag autoload.

    targets := OrderedCollection new.
    s := aFilePath asFilename readStream.
    s notNil ifTrue:[
        s := LineNumberReadStream readingFrom:s.
        [s atEnd] whileFalse:[
            lineNr := s lineNumber.
            line := s nextLine.
            l := line withoutSeparators.

            (l startsWith:'def ') ifTrue:[
                nm := l copyFrom:5.
                targets add:(Tag::TFunction 
                                label:nm 
                                pattern:nil
                                type:nil
                                lineNumber:lineNr).
            ] ifFalse:[
                (l startsWith:'class ') ifTrue:[
                    nm := l copyFrom:6.
                    targets add:(Tag::TClass 
                                    label:nm 
                                    pattern:nil
                                    type:nil
                                    lineNumber:lineNr).
                ].
            ].
        ].
        s close
    ].
    ^ targets
!

stTagsInFile:aFilePath
    "smalltalk tags:
     generate a changeList from the contents and convert it into a tag-list
    "

    |targets s|

    Tag autoload.

    targets := OrderedCollection new.
    s := aFilePath asFilename readStream.
    s notNil ifTrue:[
        s := LineNumberReadStream readingFrom:s.
        s skipSeparators.

        "/ new interface: block-arg to #changesFromStream:do: gets 3 args
        [
            ChangeSet::InvalidChangeChunkError handle:[:ex |
                Dialog warn:('Error while processing changes - skipping: ' , aFilePath asFilename pathName).
            ] do:[
                ChangeSet changesFromStream:s do:[:aChange :lNr :pos|
                    aChange isClassDefinitionChange ifTrue:[
                        targets add:(Tag::TClass 
                                        label:(aChange className) 
                                        pattern:('/subclass:')
                                        type:nil
                                        lineNumber:lNr).
                    ] ifFalse:[
                        aChange isMethodChange ifTrue:[
                            targets add:(Tag::TMethod
                                            label:(aChange selector) 
                                            pattern:('/^' , aChange selector)
                                            type:nil
                                            lineNumber:lNr).
                        ]
                    ].
                ]
            ]
        ] ensure:[
            s close.
        ].
    ].
    ^ targets
!

tclTagsInFile:aFilePath
    "tcl tags:
     naive, q&d scan for lines matching:
        proc any
    "

    |targets line l lineNr nm s words|

    Tag autoload.

    targets := OrderedCollection new.
    s := aFilePath asFilename readStream.
    s notNil ifTrue:[
        s := LineNumberReadStream readingFrom:s.
        [s atEnd] whileFalse:[
            lineNr := s lineNumber.
            line := s nextLine.
            l := line withoutSeparators.

            (l startsWith:'proc ') ifTrue:[
                nm := l copyFrom:6.
                targets add:(Tag::TFunction 
                                label:nm 
                                pattern:nil
                                type:nil
                                lineNumber:lineNr).
            ] ifFalse:[ (l startsWith:'tixWidgetClass ') ifTrue:[
                nm := l copyFrom:'tixWidgetClass ' size + 1.
                (nm endsWith:'{') ifTrue:[
                    nm := (nm copyWithoutLast:1) withoutSeparators.
                ].
                targets add:(Tag::TClass 
                                label:nm 
                                pattern:nil
                                type:nil
                                lineNumber:lineNr).
            ] ifFalse:[ (l startsWith:'set ') ifTrue:[
                hideVariables value ~~ true ifTrue:[
                    words := l asCollectionOfWords.
                    words size >= 2 ifTrue:[
                        nm := words second.
                        targets add:(Tag::TVariable 
                                        label:nm 
                                        pattern:nil
                                        type:nil
                                        lineNumber:lineNr).
                ]
            ]]]].
        ].
        s close
    ].
    ^ targets





!

yaccTagsInFile:aFilePath
    "yacc tags:
     naive, q&d scan for lines matching:
        <anything>:
    "

    |targets line l lineNr nm s words w 
       |

    Tag autoload.

    targets := OrderedCollection new.
    s := aFilePath asFilename readStream.
    s notNil ifTrue:[
        s := LineNumberReadStream readingFrom:s.
        [s atEnd] whileFalse:[
            line := s nextLine.
            l := line withoutSeparators.
            words := l asCollectionOfWords.

            words size >= 1 ifTrue:[
                w := words first.
                (w endsWith:$:) ifTrue:[
                    nm := w copyWithoutLast:1.

                    lineNr := s lineNumber - 1.
                    targets add:(Tag::TLabel
                                    label:nm 
                                    pattern:nil
                                    type:nil
                                    lineNumber:lineNr).
                ].
            ]
        ].
        s close
    ].
    ^ targets
! !

!TagList methodsFor:'testing'!

supportsFile:aFile
    "return true, if we can generate tags for a file"

    |suffix lcSuffix lcName selfClass|

    aFile isReadable ifFalse:[^ false].

    "/ cg: now always return true - let generateTag run against the wall...
    ^ true.

"/    suffix := aFile suffix.
"/    lcSuffix := suffix asLowercase.
"/
"/    selfClass := self class.
"/
"/    suffix size ~~ 0 ifTrue:[
"/        ((selfClass isCSuffix:lcSuffix) 
"/        or:[(selfClass isJavaSuffix:lcSuffix)
"/        or:[(selfClass isEiffelSuffix:lcSuffix)
"/        or:[(selfClass isFortranSuffix:lcSuffix)
"/        or:[(selfClass isPythonSuffix:lcSuffix)
"/        or:[(selfClass isLispSuffix:lcSuffix)
"/        or:[(selfClass isPrologSuffix:lcSuffix)
"/        or:[(selfClass isTCLSuffix:lcSuffix)
"/        or:[(selfClass isAssemblerSuffix:lcSuffix)
"/        or:[(selfClass isSmalltalkSuffix:lcSuffix)
"/        or:[(selfClass isRubySuffix:lcSuffix)]]]]]]]]]])
"/        ifTrue:[
"/            ^ true
"/        ].
"/    ].
"/
"/    lcName := aFile baseName asLowercase.
"/    (selfClass makeFilePatterns contains:[:pattern | pattern match:lcName]) ifTrue:[
"/        ^ true
"/    ].
"/    ^ false
! !

!TagList class methodsFor:'documentation'!

version_CVS
    ^ '$Header: /cvs/stx/stx/libtool/Tools__TagList.st,v 1.1 2011-05-06 08:36:33 cg Exp $'
! !