CharacterSetView.st
author Claus Gittinger <cg@exept.de>
Thu, 12 Feb 2004 19:36:45 +0100
changeset 2628 47ca43b03718
parent 2627 c08a4b177a2d
child 2630 6dbb2681d47f
permissions -rw-r--r--
checkin from browser

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

View subclass:#CharacterSetView
	instanceVariableNames:'codePageHolder selectedCodePointHolder'
	classVariableNames:''
	poolDictionaries:''
	category:'Collections-Text-Encodings'
!

!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 fonts characters
    (opened via the fontPanels - text-preview popUpMenu)
    or to insert characters into a textView (opened by a textEditors misc-specialCharacters menu).
"
! !

!CharacterSetView class methodsFor:'startup'!

open
    self openOn:View defaultFont

    "
     self open
    "
!

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
    |top panel v bNext bPrev bFirst bLast rangeLabel codePointLabel
     first last next prev enable update updateCodePoint w h
     minPage maxPage|

    minPage := 0.
    maxPage := 16rFF. "/ aFont isSingleByteFont ifTrue:[0] ifFalse:[16rFF].

    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.

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

    "/ actions
    updateCodePoint := [
            |selectedCodePoint|

            selectedCodePoint := v selectedCodePoint.
            selectedCodePoint isNil ifTrue:[
                codePointLabel label:clickLabel
            ] ifFalse:[
                codePointLabel label:('Selected: u%1'
                        bindWith:((selectedCodePoint printStringRadix:16) leftPaddedTo:4 with:$0)).
            ].
            codePointLabel repairDamage.
    ].

    update := [
            |uOffs selectedCodePoint|

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

    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.
        ].


    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.

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

    update value.

    v selectedCodePointHolder onChangeEvaluate:updateCodePoint.

    w := v preferredExtent x max:(panel preferredExtent x).
    h := v preferredExtent y + (panel preferredExtent y).
    top extent:(w @ h).

    top open.
    ^ v

    "
     self openOn:(View defaultFont).
    "
! !

!CharacterSetView methodsFor:'accessing'!

codePage
    ^ codePageHolder value
!

codePage:pageNr
    codePageHolder value:pageNr.
!

codePageHolder
    ^ codePageHolder
!

selectedCodePoint
    ^ selectedCodePointHolder value
!

selectedCodePointHolder
    ^ selectedCodePointHolder
! !

!CharacterSetView methodsFor:'drawing'!

redraw
    |wCol hRow dY|

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

    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.
    ].

    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 s|

            codePoint := rowBase + col.
            s := (Character value:(self codePage * 16r100) + codePoint) 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.
            ].
        ].
    ].

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

sizeChanged:how
    self clear.
    self redraw.
! !

!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.
    ].
!

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

!CharacterSetView methodsFor:'initialization'!

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

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

!CharacterSetView methodsFor:'queries'!

preferredExtent
    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.8 2004-02-12 18:36:45 cg Exp $'
! !