CharacterSetView.st
author Stefan Vogel <sv@exept.de>
Sun, 26 Oct 2008 21:12:48 +0100
changeset 3575 3682d1338906
parent 3484 7d9a3d9890f6
child 3932 6ec7e708cad5
permissions -rw-r--r--
changed #preferredExtent - use explicitExtent instvar

"
 COPYRIGHT (c) 2004 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' }"

View subclass:#CharacterSetView
	instanceVariableNames:'codePageHolder selectedCodePointHolder masterViewOrNil
		encoderOrNil'
	classVariableNames:''
	poolDictionaries:''
	category:'Views-Special'
!

!CharacterSetView class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2004 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
"
    Can be used both as an informative display of a font's characters
    (opened via the fontPanels-preview-popUpMenu)
    or to insert characters into a textView 
    (opened by a textEditors misc-specialCharacters menu).

    Author:
        Claus Gittinger
"
!

examples
"
    CharacterSetView openOn:(Button defaultFont).


    CharacterSetView 
        openAsInputFor:Transcript
        label:'Input to Transcript'
        clickLabel:'Click to input character'
"
! !

!CharacterSetView class methodsFor:'instance creation'!

new
    ^ self basicNew initialize.
! !

!CharacterSetView class methodsFor:'startup'!

open
    self openOn:(View defaultFont)

    "
     self open
    "
!

openAsInputFor:aView label:viewLabel clickLabel:clickLabel
    ^ self 
        openOn:aView font
        label:viewLabel 
        clickLabel:clickLabel
        asInputFor:aView
!

openOn:aFont
    ^ self
        openOn:aFont 
        label:aFont printString
        clickLabel:'Click on glyph to see its codePoint.'

    "
     self openOn:(View defaultFont).
    "
!

openOn:aFont label:viewLabel clickLabel:clickLabel
    ^ self 
        openOn:aFont 
        label:viewLabel 
        clickLabel:clickLabel 
        asInputFor:nil
!

openOn:aFont label:viewLabel clickLabel:clickLabel asInputFor:aView
    self
        openOn:aFont 
        label:viewLabel 
        clickLabel:clickLabel 
        asInputFor:aView 
        encoder:nil

    "
     self openOn:(View defaultFont).
     self openOn:(Font family:'courier' face:'medium' style:'roman' size:12 encoding:'iso10646-1').
    "
!

openOn:aFont label:viewLabel clickLabel:clickLabel asInputFor:aView encoder:aCharacterEncoderOrNil
    |top panel v bNext bPrev bFirst bLast rangeLabel codePointLabel
     first last next prev enable update updateCodePoint w h
     minPage maxPage insertCharacter fontMetrics minCode maxCode|

    aCharacterEncoderOrNil isNil ifTrue:[
        fontMetrics := (aFont onDevice:Screen current) getFontMetrics.
        minCode := fontMetrics minCode.
        maxCode := fontMetrics maxCode.
    ] ifFalse:[
        minCode := aCharacterEncoderOrNil minCode.
        maxCode := aCharacterEncoderOrNil maxCode.
    ].

    minPage := minCode >> 8.
    maxPage := maxCode >> 8.

    top := StandardSystemView new.
    top label:viewLabel.

    v := self origin:0.0@0.0 corner:1.0@1.0 in:top.
    v topInset:25.
    v font:aFont.
    v codePageHolder value:minPage.
    v characterEncoding:(aFont encoding).
    v encoder:aCharacterEncoderOrNil.

    panel := HorizontalPanelView in:top.
    panel origin:(0.0 @ 0.0) corner:(1.0 @ 0.0).
    panel bottomInset:-25.
    panel horizontalLayout:#left.

    aView notNil ifTrue:[
        v useSameFontAs:aView.
    ].

    "/ actions
    aView notNil ifTrue:[
        insertCharacter := [:char | 
                                (char isString ifTrue:[char] ifFalse:[Array with:char])
                                do:[:char | |unicodePoint unicodeChar|
                                    unicodePoint := CharacterEncoder encode:(char codePoint) from:aView characterEncoding into:#'unicode'.
                                    unicodeChar := Character value:unicodePoint.
                                    aView dispatchEvent:(WindowEvent keyPress:unicodeChar x:0 y:0 view:v).
                                    aView dispatchEvent:(WindowEvent keyRelease:unicodeChar x:0 y:0 view:v).
                                ].
                           ].
    ].

    updateCodePoint := [
            |selectedCodePoint selectedChar 
             isLetter isDigit isUppercase isLowercase 
             codeString decoded decodedString|

            selectedCodePoint := v selectedCodePoint.
            selectedCodePoint isNil ifTrue:[
                codePointLabel label:clickLabel
            ] ifFalse:[
                selectedChar := Character value:selectedCodePoint.
                (#('unicde' 'iso10646-1' 'iso8859-1' 'ascii') includes:(v font encoding))
                ifTrue:[
                    isLetter := selectedChar isNationalLetter.
                    isDigit := selectedChar isNationalDigit.
                    isUppercase := selectedChar isUppercase.
                    isLowercase := selectedChar isLowercase.
                ] ifFalse:[
                    isLetter := isDigit := isUppercase := isLowercase := false.     "/ actually: unknown
                ].
                aCharacterEncoderOrNil isNil ifTrue:[
                    decodedString := ''.
                    codeString := 'u' , ((selectedCodePoint printStringRadix:16) leftPaddedTo:4 with:$0)
                ] ifFalse:[
                    decoded := aCharacterEncoderOrNil decode:selectedCodePoint.
                    decodedString := 'u' , ((decoded printStringRadix:16) leftPaddedTo:4 with:$0).
                    codeString := ((selectedCodePoint printStringRadix:16) leftPaddedTo:4 with:$0)
                ].
                codePointLabel 
                    label:
                        ('Selected: %1 %2 %3 %4 %5'
                            bindWith:codeString
                            with:((selectedCodePoint printString) leftPaddedTo:5)
                            with:(isUppercase ifTrue:'Uc' ifFalse:[isLowercase ifTrue:'lc' ifFalse:''])
                            with:(isLetter ifTrue:'Letter' ifFalse:[(isDigit ifTrue:'Digit' ifFalse:'')])
                            with:decodedString
                        ).
            ].
            codePointLabel repairDamage.

            aView notNil ifTrue:[
                selectedCodePoint notNil ifTrue:[
                    insertCharacter value:(Character value:selectedCodePoint).
                    v selectedCodePointHolder setValue:nil.
                ]
            ]
    ].

    update := [
            |uOffs selectedCodePoint lbl|

            aCharacterEncoderOrNil isNil ifTrue:[
                lbl := 'u%1 ... u%2'
            ] ifFalse:[
                lbl := '%1 ... %2'
            ].
            uOffs := v codePage * 16r0100.
            rangeLabel label:(lbl 
                        bindWith:((uOffs printStringRadix:16) leftPaddedTo:4 with:$0)
                        with:(((uOffs + 16rFF) printStringRadix:16) leftPaddedTo:4 with:$0)).
            rangeLabel repairDamage.
        ].

    minPage ~~ maxPage ifTrue:[
        enable := [
                v codePage > minPage ifTrue:[ 
                    bPrev enable. 
                    bFirst enable. 
                ] ifFalse:[
                    bPrev disable. 
                    bFirst disable. 
                ].
                v codePage < maxPage ifTrue:[ 
                    bNext enable. 
                    bLast enable. 
                ] ifFalse:[
                    bNext disable. 
                    bLast disable. 
                ].
            ].
    ].

    next := [
            v codePage:(v codePage + 1). 
            enable value.
            update value.
        ].

    prev := [
            v codePage:(v codePage - 1). 
            enable value.
            update value.
        ].

    first := [
            v codePage:minPage. 
            enable value.
            update value.
        ].

    last := [
            v codePage:maxPage. 
            enable value.
            update value.
        ].

    minPage ~~ maxPage ifTrue:[
        bFirst := Button label:(ToolbarIconLibrary start16x16Icon) in:panel.
        bFirst action:first.

        bPrev := Button label:(ToolbarIconLibrary back16x16Icon) in:panel.
        bPrev controller beTriggerOnDown.
        bPrev action:prev.
        bPrev disable.
        bPrev autoRepeat:true.

        bNext := Button label:(ToolbarIconLibrary forward16x16Icon) in:panel.
        bNext controller beTriggerOnDown.
        bNext action:next.
        bNext autoRepeat:true.

        bLast := Button label:(ToolbarIconLibrary finish16x16Icon) in:panel.
        bLast action:last.
        bLast disable.
    ].

    rangeLabel := Label label:'RangeStart .. RangeStop' in:panel.
    codePointLabel := Label label:clickLabel in:panel.
    codePointLabel foregroundColor:(Color blue).

    update value.
    enable value.

    v selectedCodePointHolder onChangeEvaluate:updateCodePoint.
    v codePageHolder onChangeEvaluate:update.

    w := v preferredWidth max:(panel preferredWidth).
    h := v preferredHeight + (panel preferredHeight).
    top extent:(w @ h).

    aView notNil ifTrue:[
        top application:(aView application).
        top beSlave.
    ].
    top open.
    ^ v

    "
     self openOn:(View defaultFont).
     self openOn:(Font family:'courier' face:'medium' style:'roman' size:12 encoding:'iso10646-1').
    "

    "Modified: / 11-10-2006 / 22:30:32 / cg"
! !

!CharacterSetView methodsFor:'accessing'!

codePage
    ^ codePageHolder value
!

codePage:pageNr
    codePageHolder value:pageNr.
!

codePageHolder
    ^ codePageHolder
!

encoder:aCharacterEncoder
    encoderOrNil := aCharacterEncoder
!

selectedCodePoint
    ^ selectedCodePointHolder value
!

selectedCodePointHolder
    ^ selectedCodePointHolder
! !

!CharacterSetView methodsFor:'change & update'!

update:something with:aParameter from:changedObject
    |newFont|

    something == #font ifTrue:[
        newFont := masterViewOrNil font.
        self font:newFont.
        characterEncoding := newFont encoding.
        ^ self.
    ].
    super update:something with:aParameter from:changedObject
! !

!CharacterSetView methodsFor:'drawing'!

redraw
    |wCol hRow dY|

    wCol := width / 16.
    hRow := height / 16.

    dY := (hRow - (font height)) // 2 + (font ascent).

    0 to:15 do:[:row |
        |y0 y1 y rowBase|

        rowBase := row * 16r10.
        y := y0 := row * hRow.
        y := y rounded asInteger.
        y := y + dY.

        y1 := (row+1) * hRow.
        y1 := y1 rounded asInteger.

        0 to:15 do:[:col |
            |x0 x1 x codePoint decodedCodePoint s|

            codePoint := (self codePage * 16r100) + (rowBase + col).
            encoderOrNil notNil ifTrue:[
                decodedCodePoint := encoderOrNil decode:codePoint
            ] ifFalse:[
                decodedCodePoint := codePoint
            ].
            s := (Character value:decodedCodePoint) asString.

            x := x0 := (col * wCol) rounded asInteger.
            x := x rounded asInteger.
            x := x + (wCol / 2).
            x := x - ((font widthOf:s) // 2).

            x1 := ((col+1) * wCol) rounded asInteger.
            x1 := x1 rounded asInteger.

            codePoint == self selectedCodePoint ifTrue:[
                self paint:(Color red).
                self fillRectangle:((x0+1)@(y0+1) corner:(x1)@(y1)).
                self paint:(Color white).
                self displayString:s x:x y:y.
                self paint:(Color black).
            ] ifFalse:[
                self displayString:s x:x y:y.
            ].
        ].
    ].

    0 to:16 do:[:col |
        |x|

        x := (col * wCol) rounded asInteger.
        self displayLineFromX:x y:0 toX:x y:height-1.
    ].

    0 to:15 do:[:row |
        |y|

        y := (row * hRow) rounded asInteger.
        self displayLineFromX:0 y:y toX:width y:y.
    ].

    "
     (self extent:300@600) open
    "
!

sizeChanged:how
    super sizeChanged:how.

    self clear.
    self invalidate.
! !

!CharacterSetView methodsFor:'event handling'!

buttonPress:button x:x y:y
    |wCol hRow row col code|

    wCol := width / 16.
    hRow := height / 16.

    row := y // hRow.
    col := x // wCol.

    code := (self codePage*16r0100) + (row * 16) + col.
    selectedCodePointHolder value:code.
!

codePageChanged
    realized ifTrue:[
        self clear.
        self redraw.
    ].
!

keyPress:key x:x y:y
    |cp ncp|

    cp := selectedCodePointHolder value. 
    key == #CursorRight ifTrue:[
        ncp := (cp + 1).
    ].
    key == #CursorLeft ifTrue:[
        ncp := (cp - 1).
    ].
    key == #CursorDown ifTrue:[
        ncp := (cp + 16).
    ].
    key == #CursorUp ifTrue:[
        ncp := (cp - 16).
    ].
    ncp notNil ifTrue:[
        ncp >= 0 ifTrue:[
            ncp <= 16rFFFF ifTrue:[
                codePageHolder value:(ncp bitShift:-8).
                selectedCodePointHolder value:ncp.
            ]
        ].
        ^ self.
    ].

    super keyPress:key x:x y:y 
!

selectedCodePointChanged
    realized ifTrue:[
        self clear.
        self redraw.
    ].
! !

!CharacterSetView methodsFor:'initialization & release'!

destroy
    masterViewOrNil notNil ifTrue:[
        masterViewOrNil removeDependent:self.
        masterViewOrNil := nil.
    ].
    super destroy.
!

initialize
    super initialize.
    codePageHolder := 0 asValue.
    codePageHolder onChangeSend:#codePageChanged to:self.

    selectedCodePointHolder := ValueHolder new.
    selectedCodePointHolder onChangeSend:#selectedCodePointChanged to:self.
!

useSameFontAs:aView
    masterViewOrNil := aView.
    masterViewOrNil addDependent:self
! !

!CharacterSetView methodsFor:'queries'!

preferredExtent
    "/ If I have an explicit preferredExtent..
    explicitExtent notNil ifTrue:[
        ^ explicitExtent
    ].

    "/ If I have a cached preferredExtent value..
    preferredExtent notNil ifTrue:[
        ^ preferredExtent
    ].

    ^ ((4 + font width + 4) * 16)
       @
      ((4 + font height + 4) * 16)
! !

!CharacterSetView class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/CharacterSetView.st,v 1.24 2008-10-26 20:12:48 stefan Exp $'
! !