DoWhatIMeanSupport.st
author Claus Gittinger <cg@exept.de>
Fri, 23 May 2003 11:30:18 +0200
changeset 2515 69cbb89c127e
parent 2514 4f8d8658289a
child 2516 9f022f76308d
permissions -rw-r--r--
+isKey:nextTo: for simple typo detection

"
 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:libwidg2' }"

Object subclass:#DoWhatIMeanSupport
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'System-Support'
!

!DoWhatIMeanSupport 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.
"
!

documentation
"
    misc collected UI support (functional)


    [author:]
        Claus Gittinger (cg@exept.de)

    [instance variables:]

    [class variables:]

    [see also:]

"
! !

!DoWhatIMeanSupport class methodsFor:'rename support'!

goodRenameDefaultFor:oldName lastOld:lastOldName lastNew:lastNewName
    "generate a reasonable default for a rename operation.
     (used for rename category etc.)"

    |prefix suffix lastNewSize lastOldSize|

    lastNewName isNil ifTrue:[ ^ nil].

    lastNewSize := lastNewName size.
    lastOldSize := lastOldName size.

    (lastNewName endsWith:lastOldName) ifTrue:[
        "last rename was 
            'foo' -> 'Xfoo'
         then, a good default for
            'bar' would be 'Xbar'
        "
        prefix := lastNewName copyTo:(lastNewSize - lastOldSize).
        ^ (prefix , oldName).
    ].
    (lastOldName endsWith:lastNewName) ifTrue:[
        "last rename was 
            'Xfoo' -> 'foo'
         then, a good default for
            'Xbar' would be 'bar'
        "
        prefix := lastOldName copyTo:(lastOldSize - lastNewSize).
        (oldName startsWith:prefix) ifTrue:[
            ^ (oldName copyFrom:prefix size+1).
        ]
    ].
    (lastOldName asLowercase = lastNewName asLowercase) ifTrue:[
        (lastOldName first ~= lastNewName first) ifTrue:[
            (lastOldName first isLowercase = oldName first isLowercase) ifTrue:[
                "last rename was 
                    'xfoo' -> 'Xfoo'
                 then, a good default for
                    'xbar' would be 'Xbar'
                "
                lastOldName first isLowercase ifTrue:[
                    ^ oldName first asUppercase asString , (oldName copyFrom:2).
                ] ifFalse:[
                    ^ oldName first asLowercase asString , (oldName copyFrom:2).
                ]
            ]
        ].
    ].
    (lastOldName withoutSeparators = lastNewName) ifTrue:[
        "last rename was 
            '  foo   ' -> 'foo'
         then, a good default for
            '  bar   ' would be 'bar'
        "
        ^ oldName withoutSeparators.
    ].
    (lastNewName startsWith:lastOldName) ifTrue:[
        suffix := lastNewName copyLast:(lastNewSize - lastOldSize).
        ^ (oldName , suffix).
    ].
    (lastOldName startsWith:lastNewName) ifTrue:[
        suffix := lastOldName copyLast:(lastOldSize - lastNewSize).
        (oldName endsWith:suffix) ifTrue:[
            ^ (oldName copyWithoutLast:suffix size).
        ]
    ].

    ^ nil
!

goodRenameDefaultForFile:oldName lastOld:lastOldName lastNew:lastNewName
    "generate a reasonable default for a file rename operation.
     (Try to rename multiple files in the new fileBrowser, 
     to see what this is doing)"

    |prefix suffix t
     lastOldWOSuffix lastNewWOSuffix oldWOSuffix lastOldRest oldRest lastNewRest
     lastRemoved lastInserted default|

    default := self goodRenameDefaultFor:oldName lastOld:lastOldName lastNew:lastNewName.
    default notNil ifTrue:[ ^ default].

    lastOldWOSuffix := lastOldName asFilename withoutSuffix name.
    lastNewWOSuffix := lastNewName asFilename withoutSuffix name.
    oldWOSuffix := oldName asFilename withoutSuffix name.

    "/ suffix change ?
    lastOldWOSuffix = lastNewWOSuffix ifTrue:[
        lastOldName asFilename suffix ~= lastNewName asFilename suffix ifTrue:[
            ^ (oldName asFilename withSuffix:(lastNewName asFilename suffix)) pathName
        ].
    ].

    prefix := lastOldWOSuffix commonPrefixWith:oldWOSuffix.
    (lastNewWOSuffix startsWith:prefix) ifTrue:[
        lastOldRest := lastOldWOSuffix copyFrom:prefix size + 1.
        lastNewRest := lastNewWOSuffix copyFrom:prefix size + 1.
        oldRest := oldWOSuffix copyFrom:prefix size + 1.

        (lastNewRest endsWith:lastOldRest) ifTrue:[
            t := lastNewRest copyWithoutLast:lastOldRest size.
            ^ ((prefix , t , oldRest) asFilename withSuffix:oldName asFilename suffix) name
        ].
    ].

    suffix := lastOldWOSuffix commonSuffixWith:lastNewWOSuffix.
    suffix size > 0 ifTrue:[
        "/ last change changed something at the beginning
        prefix := oldWOSuffix commonPrefixWith:lastOldWOSuffix.
        prefix size > 0 ifTrue:[
            "/ this name starts with the same characters
            lastRemoved := lastOldWOSuffix copyWithoutLast:suffix size.
            lastInserted := lastNewWOSuffix copyWithoutLast:suffix size.
            (lastRemoved startsWith:lastInserted) ifTrue:[
                oldWOSuffix size >= lastInserted size ifTrue:[
                    ^ (oldWOSuffix copyTo:lastInserted size) , (oldName copyFrom:lastRemoved size + 1)
                ]
            ].
            ^ lastInserted , (oldName copyFrom:lastRemoved size + 1)
        ].
    ].

    ^ nil
! !

!DoWhatIMeanSupport class methodsFor:'typing distance'!

isKey:k1 nextTo:k2
    "return true, if k1 and k2 are adjacent keys on the keybaord.
     CAVEAT: hard coded us-keyboard here"

    |keys|

    "/ for now: hardcoded US keyboard (should be language dependent)
    keys := #( 'qwertyuiop'
               'asdfghjkl'
               'zxcvbnm' ).

    ^ self isKey:k1 nextTo:k2 onKeyboard:keys

    "
     self isKey:$a nextTo:$s 
     self isKey:$a nextTo:$e 
    "
!

isKey:k1 nextTo:k2 onKeyboard:keys
    "return true, if k1 and k2 are adjacent keys on the keybaord.
     CAVEAT: hard coded us-keyboard here"

    |row1 row2 col1 col2|

    row1 := keys findFirst:[:row | row includes:k1].
    row2 := keys findFirst:[:row | row includes:k2].

    (row1-row2) abs <= 1 ifFalse:[^ false].

    col1 := (keys at:row1) indexOf:k1.
    col2 := (keys at:row2) indexOf:k2.

    ^ (col1-col2) abs <= 1

    "
     self isKey:k1 nextTo:k2
    "
! !

!DoWhatIMeanSupport class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/DoWhatIMeanSupport.st,v 1.7 2003-05-23 09:30:18 cg Exp $'
! !