I extracted some old code and adapted it slightly (see below). I've  
not executed this but just typed it in Mail. And I have not completely  
read/understood your code but maybe it does what you need :)

Cheers,
Adrian


        symbols := Symbol allSymbols.
        groups := Dictionary new.
        SystemOrganization categories do: [ :cat |
                groups
                        at: cat
                        put: ((SystemOrganization superclassOrder: cat) select: 
[:c |
                                aCollection includes: c]) asArray ].
        groups keys do: [ :cat |
                roots := groups at: cat.
                roots := roots reject: [ :each | unused includes: each ].
                roots := roots , (roots collect: #class).
                (ImageSegment new
                        copyFromRoots: roots
                        sizeHint: 0
                        areUnique: true)
                                extract;
                                writeToFile: cat ]

On Jan 6, 2010, at 15:44 , Mariano Martinez Peck wrote:

> Hi folks. I will pay a beer in next ESUG to the person that helps me  
> to
> refactor this piece of code of ImageSegments:
>
> The idea is that I have a list of classes that were inactive and I  
> want to
> group them by category (actually, seeing the code I think it is  
> package) and
> to to create an ImageSegment per category (or package).
>
> This is the code (ONLYYYYY a piece...I cut all the rest)
>
> unused := self inactiveClassesDuringDiscovery.  "These are the  
> classes that
> were not used"
>    groups := Dictionary new.
>    SystemOrganization categories do:
>        [:cat |
>        i := (cat findLast: [:c | c = $-]) - 1.
>        i <= 0 ifTrue: [i := cat size].
>        groups at: (cat copyFrom: 1 to: i)
>            put: (groups at: (cat copyFrom: 1 to: i) ifAbsent: [Array  
> new])
> ,
>            ((SystemOrganization superclassOrder: cat) select: [:c |
>                unused includes: c]) asArray].
>    groups keys do:
>        [:cat | roots := groups at: cat.
>        Transcript cr; cr; show: cat; cr; print: roots; endEntry.
>        roots := roots , (roots collect: [:c | c class]).
>        "There seems to be a problem with these packages, thus they are
> excluded."
>        ((cat beginsWith: 'Sys') or: [cat beginsWith: 'Multilingual']  
> or:
> [cat beginsWith: 'Kerne'] ) ifFalse:
>            [(ImageSegment new copyFromRoots: roots sizeHint: 0)  
> extract;
>                writeToFile: cat].
>        Transcript cr; print: Smalltalk garbageCollect; endEntry]
>
>
> Can someone help me tu rewrite this? I think I could use  
> PackageOrganizer or
> PackageInfo  but I have no idea.
>
> Thanks!
>
> Mariano
> _______________________________________________
> Pharo-project mailing list
> Pharo-project@lists.gforge.inria.fr
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project


_______________________________________________
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

Reply via email to