TypeConverter.st
author penk
Mon, 10 Feb 2003 18:43:11 +0100
changeset 1695 3b54883b6392
parent 1653 f086f72cc8fa
child 1696 7dbac9fb8894
permissions -rw-r--r--
checkin from browser

"
 COPYRIGHT (c) 1997 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:libview2' }"

PluggableAdaptor subclass:#TypeConverter
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'Interface-Support-Models'
!

!TypeConverter class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1997 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
"
    a typeConverter can be used as an editFields model
    (remember, that an editField expects a string in its model),
    to convert the fields string value to some object and vice versa.
    Its main use is when building interfaces with inputFields,
    where the datum to be entered is a non-string and you
    want to have the entered value be converted automatically.
    (and vice versa, to convert the datum to a string).

    No real new functionality is added here - all is inherited
    from PluggableAdapter; however, some specialized instance creation
    methods are added here.

    Notice: 
        this class was implemented using protocol information
        from alpha testers - it may not be complete or compatible to
        the corresponding ST-80 class. 
        If you encounter any incompatibilities, please forward a note 
        describing the incompatibility verbal (i.e. no code) to the ST/X team.

    [author:]
        Claus Gittinger
"


!

examples 
"
    convert a number to a string:
                                                                        [exBegin]
        |v t i|

        v := 1 asValue.

        t := HorizontalPanelView new.
        t extent:200@50.
        t horizontalLayout:#fitSpace.

        i := EditField in:t.
        i model:(TypeConverter onNumberValue:v).
        t open.

        (Delay forSeconds:3) wait.
        v value:2.
                                                                        [exEnd]
    convert a number to a string with range:
                                                                        [exBegin]
        |v t i|

        v := 1 asValue.

        t := HorizontalPanelView new.
        t extent:200@50.
        t horizontalLayout:#fitSpace.

        i := EditField in:t.
        i model:(TypeConverter onNumberValue:v minValue:0 maxValue:100).
        t open.

        (Delay forSeconds:3) wait.
        v value:2.
                                                                        [exEnd]
    convert a date to a string:
                                                                        [exBegin]
        |d v|

        v := nil asValue.

        d := DialogBox new.
        d addInputFieldOn:(TypeConverter onDateValue:v).
        d addOkButton.
        d open.
        d accepted ifTrue:[
            Transcript showCR:v value
        ]
                                                                        [exEnd]
"
! !

!TypeConverter class methodsFor:'instance creation'!

onDateValue:aValueHolder
    "create and return a typeConverter, which retrieves
     a date via #value, and converts
     a date-string to a date via #value:.
     Useful as an editFields model, which operates on some
     date value (or aspectAdaptor, which adapts to a numeric slot)"

    ^ (self on:aValueHolder) dateToText

    "Modified: 21.2.1997 / 18:46:11 / cg"
    "Created: 4.3.1997 / 12:30:49 / cg"
!

onNumberValue:aValueHolder
    "create and return a typeConverter, which retrieves
     a values string representation via #value, and converts
     a number-string to a value via #value:.
     Useful as an editFields model, which operates on some
     numeric value (or aspectAdaptor, which adapts to a numeric slot)"

    ^ (self on:aValueHolder) numberToText

    "Modified: 21.2.1997 / 18:46:11 / cg"
!

onNumberValue:aValueHolder format:formatString
    "create and return a typeConverter, which retrieves
     a values string representation via #value, and converts
     a number-string to a value via #value:.
     Useful as an editFields model, which operates on some
     numeric value (or aspectAdaptor, which adapts to a numeric slot)"

    ^ (self on:aValueHolder) numberToTextFormattedBy:formatString

    "Created: 4.3.1997 / 11:51:25 / cg"
    "Modified: 4.3.1997 / 11:51:41 / cg"
!

onNumberValue:aValueHolder leftPaddedTo:aSize with:aCharacter
    "create and return a typeConverter, which retrieves
     a values string representation via #value, and converts
     a number-string to a value via #value:.
     Useful as an editFields model, which operates on some
     numeric value (or aspectAdaptor, which adapts to a numeric slot)"

    ^ (self on:aValueHolder) numberToTextLeftPaddedTo:aSize with:aCharacter

"
  |m|
  m := 5 asValue.
  ((EditField model:(TypeConverter onNumberValue:m leftPaddedTo:2 with:$-)) width:100) openAt:(200@200).
  m inspect.
"
!

onNumberValue:aValueHolder minValue:min maxValue:max
    "create and return a typeConverter, which retrieves
     a values string representation via #value, and converts
     a number-string to a value via #value:.
     Useful as an editFields model, which operates on some
     numeric value (or aspectAdaptor, which adapts to a numeric slot)"

    ^ (self on:aValueHolder) numberToTextMinValue:min maxValue:max

    "Created: 4.3.1997 / 11:51:25 / cg"
    "Modified: 4.3.1997 / 11:51:41 / cg"
!

onNumberValue:aValueHolder postDecimalDigits:numPostDecimalDigits
    "create and return a typeConverter, which retrieves
     a values string representation via #value, and converts
     a number-string to a value via #value:.
     Useful as an editFields model, which operates on some
     numeric value (or aspectAdaptor, which adapts to a numeric slot)"

    ^ (self on:aValueHolder) numberToText:numPostDecimalDigits

    "Modified: / 21.2.1997 / 18:46:11 / cg"
    "Created: / 5.12.1997 / 02:55:18 / cg"
!

onSymbolValue:aValueHolder
    "create and return a typeConverter, which retrieves
     a symbol-values string representation via #value, and converts
     a string to a symbol via #value:.
     Useful as an editFields model, which operates on some
     numeric value (or aspectAdaptor, which adapts to a numeric slot)"

    ^ (self on:aValueHolder) symbolOrNil

    "Modified: 21.2.1997 / 18:46:11 / cg"
!

onTimeValue:aValueHolder
    "create and return a typeConverter, which retrieves
     a time via #value, and converts
     a time-string to a time via #value:.
     Useful as an editFields model, which operates on some
     date value (or aspectAdaptor, which adapts to a numeric slot)"

    ^ (self on:aValueHolder) timeToText

    "Modified: 21.2.1997 / 18:46:11 / cg"
    "Created: 4.3.1997 / 11:52:10 / cg"
! !

!TypeConverter methodsFor:'accessing'!

subject
    "return the cobverted subject"

    ^ model

    "Created: 21.2.1997 / 18:45:12 / cg"
!

value:newValue
    "convert and change"

    self setValue:newValue

    "Created: 21.2.1997 / 18:45:39 / cg"
! !

!TypeConverter methodsFor:'input testing'!

setNumberValue: value inModel: model fromInput: string
    "for invalid numbers, the model is set to nil. 
     By this, the dependents are forced to update their contents
     (that is: a bad input string will lead to a cleared input field here)."

    |lastInputChar needChange|

    string notEmpty ifTrue:[
        1 to: string size - 1 do: [:i| (string at: i) isLetter ifTrue: [needChange := true]].
        lastInputChar := string at: string size.
        (lastInputChar isDigit not and: [lastInputChar isPrintable and: [
        (string size > 1               or: [lastInputChar ~~ $-])  and: [
        (string occurrencesOf: $.) > 1 or: [lastInputChar ~~ $.]]]]) ifTrue: [needChange := true].
    ].

    needChange == true ifTrue:[
        value notNil ifTrue:[
            model setValue:nil
        ] ifFalse:[
            model value isNil ifTrue:[
                model changed:#value.
                ^ self
            ]
        ].
    ].
    model value:value
! !

!TypeConverter methodsFor:'standard converters'!

arrayLiteralOrStringOrSymbolOrNil
    "setup the converter to convert from a string to either a literal
     Array, a String or a symbol and vice versa. 
     Invalid strings (i.e. empty) are converted to nil;
     nil values are converted to an empty string.
     This is a very special converter (for the GUI builder) 
     - probably not belonging to here"

    self
        getBlock:[:model |
                |symbolValue|

                (symbolValue := model value) isNil ifTrue:[
                    String new
                ] ifFalse:[
                    symbolValue storeString
                ]]

        putBlock:
                [:model :string |

                |value s|

                string isEmpty ifTrue:[
                    value := nil
                ] ifFalse:[
                    s := string withoutSeparators.
                    (s startsWith:'#(') ifTrue:[
                        value := Array readFrom:s onError:nil
                    ] ifFalse:[
                        (s startsWith:'''') ifTrue:[
                            value := String readFrom:s onError:nil
                        ] ifFalse:[
                            (s startsWith:'#') ifTrue:[
                                s := s copyFrom:2
                            ].
                            value := s asSymbol
                        ]
                    ]
                ].
                model value:value]

        updateBlock: [:m :a :p | true]

    "Modified: / 26.10.1997 / 13:50:32 / cg"
    "Created: / 26.10.1997 / 14:01:02 / cg"
!

arrayLiteralOrSymbolOrNil
    "setup the converter to convert from a string to either a literal
     Array or a symbol and vice versa. 
     Invalid strings (i.e. empty) are converted to nil;
     nil values are converted to an empty string.
     This is a very special converter (for the GUI builder) 
     - probably not belonging to here"

    self
        getBlock:[:model |
                |symbolValue|

                (symbolValue := model value) isNil ifTrue:[
                    String new
                ] ifFalse:[
                    symbolValue isArray ifTrue:[
                        symbolValue storeString
                    ] ifFalse:[
                        '#' , symbolValue asString
                    ]
                ]]

        putBlock:
                [:model :string |

                |value s|

                string isEmpty ifTrue:[
                    value := nil
                ] ifFalse:[
                    s := string withoutSeparators.
                    (s startsWith:'#(') ifTrue:[
                        value := Array readFrom:s onError:nil
                    ] ifFalse:[
                        (s startsWith:'#') ifTrue:[
                            s := s copyFrom:2
                        ].
                        value := s asSymbol
                    ]
                ].
                model value:value]

        updateBlock: [:m :a :p | true]

    "Modified: / 26.10.1997 / 13:50:32 / cg"
    "Created: / 26.10.1997 / 14:01:02 / cg"
!

dateDDMMYYYY
    "setup the converter to convert from a string to a date formatted by printFormat
     DD-MM-YYYY; see also Date>>printFormat:"

    self dateToTextFormattedBy: #(1 2 3 $- 1 1 true)
!

dateMMDDYYYY
    "setup the converter to convert from a string to a date formatted by printFormat
     MM:DD:YYYY; see also Date>>printFormat:"

    self dateToTextFormattedBy: #(2 1 3 $/ 1 1 true)
!

dateOrNil
    "setup the converter to convert from a string to a date
     and vice versa. Invalid dates are converted to nil; likewise,
     a nil date is converted to an empty string."

    self
        getBlock:[:model |
                |date|

                (date := model value) isNil ifTrue:[
                    ''
                ] ifFalse:[
                    date printString
                ]]

        putBlock:
                [:model :string |

                |value|

                string isEmpty ifTrue:[
                    value := nil
                ] ifFalse:[
                    value := Date readFrom:string onError:nil
                ].
                model value:value]

        updateBlock: [:m :a :p | true]

    "Created: / 4.3.1997 / 11:56:36 / cg"
    "Modified: / 26.10.1997 / 13:51:06 / cg"
!

dateToText
    "setup the converter to convert from a string to a date
     and vice versa. Nil is converted to todays date-string,
     likewise, an empty string is converted back to todays date."

    self
        getBlock:[:model |
                |date|

                (date := model value) isNil ifTrue:[
                    Date today printString
                ] ifFalse:[
                    date printString
                ]]

        putBlock:
                [:model :string |

                |value|

                string isEmpty ifTrue:[
                    value := Date today
                ] ifFalse:[
                    value := Date readFrom:string onError:Date today
                ].
                model value:value]

        updateBlock: [:m :a :p | true]

    "Created: / 4.3.1997 / 12:32:19 / cg"
    "Modified: / 26.10.1997 / 13:52:00 / cg"
!

dateToTextFormattedBy: printFormat
    "setup the converter to convert from a string to a date formatted by printFormat
     and vice versa. Nil is converted to todays date-string,
     likewise, an empty string is converted back to todays date."

    self
        getBlock:[:model |
                    (model value ? Date today) printFormat:printFormat
                ]

        putBlock:
                [:model :string |

                |value|

                string isEmpty ifTrue:[  
                    value := Date today
                ] ifFalse:[                      
                    value := Date readFrom:string printFormat:printFormat onError:[Date today]
                ].
                model value:value]

        updateBlock: [:m :a :p | true]
!

hexadecimal
    "setup the converter to convert from a hexadecimal string to a number
     and vice versa."

    self
        getBlock:[:model |
                |hexValue|

                (hexValue := model value) isNumber ifFalse:[
                    String new
                ] ifTrue:[  
                    hexValue hexPrintString
                ]]

        putBlock:
                [:model :string |

                |value|

                string isEmpty ifTrue:[
                    value := 0
                ] ifFalse:[     
                    value := Integer readFrom: string radix:16 onError:[0]
                ].
                model value:value]

        updateBlock: [:m :a :p | true]

   
!

literal
    "setup the converter to convert from a string to a literal
     and vice versa. Invalid symbols (i.e. empty) are converted to nil;
     nil values are converted to an empty string.
     true, false, Numbers are parsed"

    self
        getBlock:[:model |
                |val s|

                val := model value.
                (val isLiteral and:[val notNil]) ifTrue:[
                    val isSymbol ifTrue:[
                        "print 'special' symbols as symbols i.e. as #'symbol'"
                        (s := val storeString) second == $' ifTrue:[
                            s
                        ] ifFalse:[
                            val printString
                        ]
                    ] ifFalse:[
                        val storeString
                    ].
                ] ifFalse:[
                    ''.
                ]]

        putBlock:
                [:model :string |

                |value s|

                string size == 0 ifTrue:[
                    value := nil
                ] ifFalse:[
                    s := string withoutSeparators.
                    "be careful, #readFrom:onError: returns nil for an undefined identifier"
                    s = 'true' ifTrue:[
                        value := true.
                    ] ifFalse:[s = 'false' ifTrue:[
                        value := false.
                    ] ifFalse:[s = 'nil' ifTrue:[
                        value := nil.
                    ] ifFalse:[s first isLetter ifTrue:[
                        value := s asSymbol.
                    ] ifFalse:[
                        value := Object readFrom:s onError:[
                            s asSymbol
                        ].
                    ]]]].
                ].
                model value:value]

        updateBlock: [:m :a :p | true]

    "Created: / 21.2.1997 / 18:58:38 / cg"
    "Modified: / 26.5.1998 / 15:06:06 / cg"
!

number
    "setup the converter to convert from a string to a number
     and vice versa. Invalid numbers are converted to nil."

    self numberToText

    "Created: 4.4.1997 / 12:46:14 / cg"
!

numberOrNil
    "setup the converter to convert from a string to a number
     and vice versa. Invalid numbers are converted to nil."

    self
        getBlock:[:model |
                |numericValue|

                (numericValue := model value) isNil ifTrue:[
                    String new
                ] ifFalse:[
                    numericValue printString
                ]]

        putBlock:
                [:model :string |

                |value|

                string size > 0 ifTrue:[
                    value := Number readFrom:string onError:nil
                ]. 
                model value:value]

        updateBlock: [:m :a :p | true]

    "Created: 21.2.1997 / 18:58:38 / cg"
!

numberOrNilToTextMinValue:minVal maxValue:maxVal
    "setup the converter to convert from a string to a number or nil
     and vice versa, but clamping the number into the range."

    self
        getBlock:[:model |
                |numericValue|

                (numericValue := model value) isNil ifTrue:[
                    String new
                ] ifFalse:[
                    numericValue printString
                ]]

        putBlock:
                [:model :string |

                |value c|

                (string isEmpty or:[string isBlank]) ifTrue:[
                    value := nil
                ] ifFalse:[
                    value := Number readFromString:string onError:[nil]. 
                    value isNil ifTrue:[
                        
                    ] ifFalse:[
                        minVal notNil ifTrue:[
                            (value < minVal and: [string notEmpty]) ifTrue: [model setValue:nil].
                            value := value max:minVal.
                        ].
                        maxVal notNil ifTrue:[
                            (value > maxVal and: [string notEmpty]) ifTrue: [model setValue:nil].
                            value := value min:maxVal.
                        ].
                    ].
                ].
                self setNumberValue: value inModel: model fromInput: string.
                ]

        updateBlock: [:m :a :p | true]

    "Modified: 21.2.1997 / 18:59:44 / cg"
!

numberOrPointOrNil
    "setup the converter to convert from a string to a number or point
     and vice versa. Invalid numbers/points are converted to nil."

    self
        getBlock:[:model |
                |value|

                (value := model value) isNil ifTrue:[
                    String new
                ] ifFalse:[
                    value printString
                ]]

        putBlock:
                [:model :string |

                |value|

                string size > 0 ifTrue:[
                    value := Point readFrom:string onError:[
                        Number readFrom:string onError:nil
                    ]
                ]. 
                model value:value]

        updateBlock: [:m :a :p | true]

    "Created: / 5.2.2000 / 01:26:48 / cg"
!

numberOrStringOrSymbolOrNil
    "setup the converter to convert from a string to either a numeric literal
     or a symbol and vice versa. 
     Invalid strings (i.e. empty) are converted to nil;
     nil values are converted to an empty string.
     This is a very special converter (for the GUI builder) 
     - probably not belonging to here"

    self
        getBlock:[:model |
                |litValue|

                (litValue := model value) isNil ifTrue:[
                    String new
                ] ifFalse:[
                    litValue storeString
                ]]

        putBlock:
                [:model :string |

                |value s|

                string isEmpty ifTrue:[
                    value := nil
                ] ifFalse:[
                    value := Number readFrom:string onError:nil.
                    value isNil ifTrue:[
                        s := string withoutSeparators.
                        (s startsWith:'''') ifTrue:[
                            value := String readFrom:s readStream onError:nil
                        ] ifFalse:[
                            (s startsWith:'#') ifTrue:[
                                s := s copyFrom:2.
                                (s startsWith:$') ifTrue:[
                                    s := s copyFrom:2 to:(s size - 1)
                                ].
                            ].
                            value := s asSymbol
                        ]
                    ]
                ].
                model value:value]

        updateBlock: [:m :a :p | true]

    "Modified: / 26.10.1997 / 13:50:32 / cg"
    "Created: / 29.10.1997 / 15:49:26 / cg"
!

numberOrSymbolOrNil
    "setup the converter to convert from a string to either a numeric literal
     or a symbol and vice versa. 
     Invalid strings (i.e. empty) are converted to nil;
     nil values are converted to an empty string.
     This is a very special converter (for the GUI builder) 
     - probably not belonging to here"

    self
        getBlock:[:model |
                |litValue|

                (litValue := model value) isNil ifTrue:[
                    String new
                ] ifFalse:[
                    litValue storeString
                ]]

        putBlock:
                [:model :string |

                |value s|

                string isEmpty ifTrue:[
                    value := nil
                ] ifFalse:[
                    value := Number readFrom:string onError:nil.
                    value isNil ifTrue:[
                        s := string withoutSeparators.
                        (s startsWith:'#') ifTrue:[
                            s := s copyFrom:2.
                            (s startsWith:$') ifTrue:[
                                s := s copyFrom:2 to:(s size - 1)
                            ].
                        ].
                        value := s asSymbol
                    ]
                ].
                model value:value]

        updateBlock: [:m :a :p | true]

    "Modified: / 26.10.1997 / 13:50:32 / cg"
    "Created: / 29.10.1997 / 15:49:26 / cg"
!

numberToText
    "setup the converter to convert from a string to a number
     and vice versa."

    self
        getBlock:[:model |
                |numericValue|

                (numericValue := model value) isNumber ifFalse:[
                    String new
                ] ifTrue:[
                    numericValue printString
                ]]

        putBlock:
                [:model :string |

                |value|

                string isEmpty ifTrue:[
                    value := 0
                ] ifFalse:[
                    value := Number readFromString: string onError:[0]
                ].
                model value:value]

        updateBlock: [:m :a :p | true]

    "Created: / 21.2.1997 / 18:57:05 / cg"
    "Modified: / 29.10.1997 / 15:49:21 / cg"
!

numberToText:numberOfPostDecimals
    "setup the converter to convert from a string to a number
     and vice versa."

    self
        getBlock:[:model |
                |numericValue|

                (numericValue := model value) isNumber ifFalse:[
                    String new
                ] ifTrue:[
                    (numericValue asFixedPoint:numberOfPostDecimals) printString
                ]]

        putBlock:
                [:model :string |

                |value|

                string isEmpty ifTrue:[
                    value := 0
                ] ifFalse:[     
                    value := Number readFromString:string onError:[0]
                ].
                self setNumberValue: value inModel: model fromInput: string.
                ]

        updateBlock: [:m :a :p | true]

    "Created: / 5.12.1997 / 02:54:13 / cg"
    "Modified: / 5.12.1997 / 18:21:04 / cg"
!

numberToTextFormattedBy:formatString
    "setup the converter to convert from a string to a number
     and vice versa, using formatString.
     The formatString is currently ignored when numbers are converted
     from a string."

    self
        getBlock:[:model |
                |numericValue|

                (numericValue := model value) isNil ifTrue:[
                    String new
                ] ifFalse:[
                    PrintConverter print:numericValue formattedBy:formatString
                ]]

        putBlock:
                [:model :string |

                |value|

                string isEmpty ifTrue:[
                    value := 0
                ] ifFalse:[          
                    value := Number readFromString: string onError:[0]. "asNumberFromFormatString:formatString"
                ].
                model value:value]

        updateBlock: [:m :a :p | true]

    "Modified: 21.2.1997 / 18:59:44 / cg"
!

numberToTextLeftPaddedTo:aSize with:aCharacter
    "setup the converter to convert from a string to a number
     and vice versa, using formatString.
     The formatString is currently ignored when numbers are converted
     from a string."

    self
        getBlock:[:model |
                |numericValue|

                (numericValue := model value) isNil ifTrue:[
                    String new
                ] ifFalse:[
                    numericValue printStringLeftPaddedTo:aSize with:aCharacter
                ]]

        putBlock:
                [:model :string |

                |value|

                string isEmpty ifTrue:[
                    value := 0
                ] ifFalse:[          
                    value := Number readFromString: string onError:[0]. "asNumberFromFormatString:formatString"
                ].
                model value:value]

        updateBlock: [:m :a :p | true]

    "Modified: 21.2.1997 / 18:59:44 / cg"
!

numberToTextMinValue:minVal maxValue:maxVal
    "setup the converter to convert from a string to a number
     and vice versa, but clamping the number into the range."

    self
        getBlock:[:model |
                |numericValue|

                (numericValue := model value) isNil ifTrue:[
                    String new
                ] ifFalse:[
                    numericValue printString
                ]]

        putBlock:
                [:model :string |

                |value c|

                string isEmpty ifTrue:[
                    value := 0
                ] ifFalse:[
                    value := Number readFromString: string onError:[0]. 
                ].               
                minVal notNil ifTrue:[
                    (value < minVal and: [string notEmpty]) ifTrue: [model setValue:nil].
                    value := value max:minVal.
                ].
                maxVal notNil ifTrue:[
                    (value > maxVal and: [string notEmpty]) ifTrue: [model setValue:nil].
                    value := value min:maxVal.
                ].
                self setNumberValue: value inModel: model fromInput: string.
                ]

        updateBlock: [:m :a :p | true]

    "Modified: 21.2.1997 / 18:59:44 / cg"
!

smalltalkObject
    "setup the converter to convert from a string to any smalltalk object
     and vice versa. The string used is the objects storeString.
     Invalid strings (i.e. empty) are converted to nil.
     This is a very special converter (for the GUI builder) 
     - probably not belonging to here"

    self
        getBlock:[:model | |v s|
                     v := model value.
                     v isNil ifTrue:[
                        s := ''
                     ] ifFalse:[
                            s := v storeString.
                            (v isString or:[v isNumber]) ifFalse:[
                                s := s , ' "' , v class name , '" '
                            ]
                     ].
                     s
                 ]

        putBlock:
                [:model :string |

                    |value|

                    string size > 0 ifTrue:[
                        value := Object readFrom:string onError:nil.
                        value isNil ifTrue:[
                            string size > 0 ifTrue:[
                                value := string
                            ]
                        ].
                    ].
                    model value:value
                ]

        updateBlock: [:m :a :p | true]

    "Modified: / 26.10.1997 / 13:50:32 / cg"
    "Created: / 29.10.1997 / 15:50:16 / cg"
!

smalltalkObjectOrNil
    "setup the converter to convert from a string to any smalltalk object
     and vice versa. The string used is the objects storeString.
     Invalid strings (i.e. empty) are converted to nil.
     This is a very special converter (for the GUI builder) 
     - probably not belonging to here"

    self
        getBlock:[:model | |v s|
                     v := model value.
                     v isNil ifTrue:[
                        s := 'nil'
                     ] ifFalse:[
                            s := v storeString.
                            (v isString or:[v isNumber]) ifFalse:[
                                s := s , ' "' , v class name , '" '
                            ]
                     ].
                     s
                 ]

        putBlock:
                [:model :string |

                    |value|

                    string size > 0 ifTrue:[
                        value := Object readFrom:string onError:[
                                                                   string size > 0 ifTrue:[
                                                                       value := string
                                                                   ]
                                                                ].
                    ].
                    model value:value
                ]

        updateBlock: [:m :a :p | true]

    "Modified: / 26.10.1997 / 13:50:32 / cg"
    "Created: / 29.10.1997 / 15:50:16 / cg"
!

symbolOrBooleanOrNil
    "setup the converter to convert from a string to a symbol or boolean
     and vice versa. Invalid symbols (i.e. empty) are converted to nil;
     nil values are converted to an empty string.
     In addition, the strings true/false convert to/from booleans."

    self
        getBlock:[:model |
                |symbolValue|

                ((symbolValue := model value) isSymbol 
                or:[symbolValue isBoolean]) 
                ifFalse:[
                    ''
                ] ifTrue:[
                    symbolValue printString. "/ storeString
                ]]

        putBlock:
                [:model :string |

                |value s|

                string size == 0 ifTrue:[
                    value := nil
                ] ifFalse:[
                    s := string withoutSeparators.
                    (s startsWith:'#') ifTrue:[
                        s := s copyFrom:2.
                        (s startsWith:$') ifTrue:[
                            s := s copyFrom:2 to:(s size - 1)
                        ].
                        value := s asSymbol
                    ] ifFalse:[
                        (#('true' 'false') includes:s) ifTrue:[
                            value := Object readFromString:s.
                        ] ifFalse:[
                            value := s asSymbol
                        ]
                    ].
                ].
                model value:value]

        updateBlock: [:m :a :p | true]

    "Created: / 21.2.1997 / 18:58:38 / cg"
    "Modified: / 26.5.1998 / 15:06:06 / cg"
!

symbolOrNil
    "setup the converter to convert from a string to a symbol
     and vice versa. Invalid symbols (i.e. empty) are converted to nil;
     nil values are converted to an empty string."

    self
        getBlock:[:model |
                |symbolValue|

                (symbolValue := model value) isSymbol ifFalse:[
                    String new
                ] ifTrue:[
                    symbolValue printString. "/ storeString
                ]]

        putBlock:
                [:model :string |

                |value s|

                string size == 0 ifTrue:[
                    value := nil
                ] ifFalse:[
                    s := string withoutSeparators.
                    (s startsWith:'#') ifTrue:[
                        s := s copyFrom:2.
                        (s startsWith:$') ifTrue:[
                            s := s copyFrom:2 to:(s size - 1)
                        ]
                    ].
                    value := s asSymbol
                ].
                model value:value]

        updateBlock: [:m :a :p | true]

    "Created: / 21.2.1997 / 18:58:38 / cg"
    "Modified: / 26.5.1998 / 15:06:06 / cg"
!

time12H
    "setup the converter to convert from a string to a time formatted by 12 hours
     and vice versa."

    self timeToTextFormattedBy: #printString12HourFormat


!

time24H
    "setup the converter to convert from a string to a time formatted by 24 hours
     and vice versa."

    self timeToTextFormattedBy: #printString24HourFormat


!

timeOrNil
    "setup the converter to convert from a string to a time
     and vice versa."

    self
        getBlock:[:model |
                |time|

                (time := model value) isNil ifTrue:[
                    ''
                ] ifFalse:[
                    time printString
                ]]

        putBlock:
                [:model :string |

                |value|

                string isEmpty ifTrue:[
                    value := nil
                ] ifFalse:[
                    value := Time readFrom:string onError:nil
                ].
                model value:value]

        updateBlock: [:m :a :p | true]

    "Created: 4.3.1997 / 11:52:47 / cg"
    "Modified: 4.3.1997 / 12:05:48 / cg"
!

timeToText
    "setup the converter to convert from a string to a time
     and vice versa."

    self timeToTextFormattedBy: #printString
!

timeToTextFormattedBy: format
    "setup the converter to convert from a string to a time formatted by format
     and vice versa."

    self
        getBlock:[:model |
                |time|

                (time := model value) isNil ifTrue:[
                    Time now perform: format
                ] ifFalse:[
                    time perform: format
                ]]

        putBlock:
                [:model :string |

                |value|

                string isEmpty ifTrue:[
                    value := Time now
                ] ifFalse:[              
                    value := Time readFrom:string onError:[Time now]
                ].
                model value:value]

        updateBlock: [:m :a :p | true]

    "Modified: 21.2.1997 / 18:59:06 / cg"
    "Created: 4.3.1997 / 11:52:47 / cg"
! !

!TypeConverter class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libview2/TypeConverter.st,v 1.40 2003-02-10 17:43:11 penk Exp $'
! !